Changeset 3373 for palm/trunk


Ignore:
Timestamp:
Oct 18, 2018 3:25:56 PM (6 years ago)
Author:
kanani
Message:

Fix cpp directives and error messages

Location:
palm/trunk/SOURCE
Files:
2 edited

Legend:

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

    r3337 r3373  
    2727! -----------------
    2828! $Id$
     29! Fix wrong location of __netcdf directive
     30!
     31! 3337 2018-10-12 15:17:09Z kanani
    2932! (from branch resler)
    3033! Formatting
     
    6568    USE kinds
    6669
    67 #if defined ( __netcdf )
    68 
    6970    USE netcdf_data_input_mod,                                                  &
    7071       ONLY: chem_emis_att_type, chem_emis_val_type
    7172
     73#if defined ( __netcdf )
    7274    USE NETCDF
    73 
    7475#endif
    7576
     
    779780 SUBROUTINE chem_emissions_init(emt_att,emt,nspec_out)
    780781
    781 #if defined( __netcdf )
     782
    782783
    783784    USE surface_mod,                                                           &
     
    798799 
    799800    INTEGER(iwp)                                                      :: ispec     !> Index to go through the emission chemical species
    800 
     801#if defined( __netcdf )
    801802
    802803!-- Actions for initial runs : TBD: needs to be updated
     
    918919 IMPLICIT NONE
    919920
    920 #if defined( __netcdf )
     921
    921922 
    922923    !--- IN/OUT
     
    983984    REAL(wp), PARAMETER   ::  ratio2ppm  = 1.0e06_wp 
    984985    !------------------------------------------------------   
    985 
     986#if defined( __netcdf )
    986987    IF ( emission_output_required ) THEN
    987988
  • palm/trunk/SOURCE/chemistry_model_mod.f90

    r3318 r3373  
    2727! -----------------
    2828! $Id$
     29! Remove MPI_Abort, replace by message
     30!
     31! 3318 2018-10-08 11:43:01Z sward
    2932! Fixed faulty syntax of message string
    3033!
     
    176179
    177180 MODULE chemistry_model_mod
    178     USE MPI
    179181
    180182    USE kinds,              ONLY: wp, iwp
     
    10181020                     (variable(char_len-2:) == '_xz')               .OR.                              &
    10191021                     (variable(char_len-2:) == '_yz') ) )               THEN             
    1020 
    1021                    IF(myid == 0)  WRITE(6,*) 'Output of species ' // TRIM(variable)  //               &
    1022                                                             TRIM(chem_species(lsp)%name)       
     1022!
     1023!--   todo: remove or replace by "CALL message" mechanism (kanani)
     1024!                    IF(myid == 0)  WRITE(6,*) 'Output of species ' // TRIM(variable)  //               &
     1025!                                                             TRIM(chem_species(lsp)%name)       
    10231026                IF (av == 0) THEN
    10241027                   DO  i = nxl, nxr
     
    10961099       DO lsp=1,nspec
    10971100          IF (TRIM(spec_name) == TRIM(chem_species(lsp)%name))   THEN
    1098              IF(myid == 0 .AND. chem_debug0 )  WRITE(6,*) 'Output of species ' // TRIM(variable)  //  &
    1099                                                           TRIM(chem_species(lsp)%name)       
     1101!
     1102!--   todo: remove or replace by "CALL message" mechanism (kanani)
     1103!              IF(myid == 0 .AND. chem_debug0 )  WRITE(6,*) 'Output of species ' // TRIM(variable)  //  &
     1104!                                                           TRIM(chem_species(lsp)%name)       
    11001105             
    11011106             IF (av == 0) THEN
     
    11681173       DO lsp=1,nspec
    11691174          IF (TRIM(spec_name) == TRIM(chem_species(lsp)%name) )               THEN             
    1170 
    1171                 IF(myid == 0 .AND. chem_debug0 )  WRITE(6,*) 'Output of species ' // TRIM(variable)  // &
    1172                                                           TRIM(chem_species(lsp)%name)       
     1175!
     1176!--   todo: remove or replace by "CALL message" mechanism (kanani)
     1177!                 IF(myid == 0 .AND. chem_debug0 )  WRITE(6,*) 'Output of species ' // TRIM(variable)  // &
     1178!                                                           TRIM(chem_species(lsp)%name)       
    11731179             IF (av == 0) THEN
    11741180                DO  i = 1, mask_size_l(mid,1)
     
    14791485       DO lsp = 1, nphot
    14801486          phot_frequen(lsp)%name = phot_names(lsp)
     1487!
     1488!--   todo: remove or replace by "CALL message" mechanism (kanani)
    14811489!         IF( myid == 0 )  THEN
    14821490!            WRITE(6,'(a,i4,3x,a)')  'Photolysis: ',lsp,trim(phot_names(lsp))
     
    16511659             tmp_phot(:,lph) = phot_frequen(lph)%freq(nzb+1:nzt,j,i)               
    16521660          ENDDO
    1653 
    1654           IF(myid == 0 .AND. chem_debug0 ) THEN
    1655              IF (i == 10 .and. j == 10) WRITE(0,*) 'begin chemics step ',dt_3d
    1656           ENDIF
     1661!
     1662!--   todo: remove (kanani)
     1663!           IF(myid == 0 .AND. chem_debug0 ) THEN
     1664!              IF (i == 10 .and. j == 10) WRITE(0,*) 'begin chemics step ',dt_3d
     1665!           ENDIF
    16571666
    16581667!--       Compute length of time step
     
    16701679             IF( simulated_time <= 2*dt_3d)  THEN
    16711680                 rcntrl_local = 0
    1672                  WRITE(9,'(a,2f10.3)') 'USE Default rcntrl in the first steps ',simulated_time,dt_3d
     1681!
     1682!--   todo: remove (kanani)
     1683!                  WRITE(9,'(a,2f10.3)') 'USE Default rcntrl in the first steps ',simulated_time,dt_3d
    16731684             ELSE
    16741685                 rcntrl_local = rcntrl
     
    18451856          solver_type = 'Rang3'
    18461857       ELSE
    1847           IF(myid == 0)  write(0,*) 'illegal solver type '     !kk chane to PALM error message
    1848           call MPI_Abort (MPI_COMM_WORLD, 1, ier)
     1858           message_string = 'illegal solver type'
     1859           CALL message( 'chem_parin', 'PA0506', 1, 2, 0, 6, 0 )
    18491860       END IF
    18501861
    1851        write(text,*) 'gas_phase chemistry: solver_type = ',trim(solver_type)
     1862!
     1863!--   todo: remove or replace by "CALL message" mechanism (kanani)
     1864!       write(text,*) 'gas_phase chemistry: solver_type = ',trim(solver_type)
    18521865!kk    Has to be changed to right calling sequence
    18531866!kk       CALL location_message( trim(text), .FALSE. )
    1854        IF(myid == 0)   THEN
    1855           write(9,*) ' '
    1856           write(9,*) 'kpp setup '
    1857           write(9,*) ' '
    1858           write(9,*) '    gas_phase chemistry: solver_type = ',trim(solver_type)
    1859           write(9,*) ' '
    1860           write(9,*) '    Hstart  = ',rcntrl(3)
    1861           write(9,*) '    FacMin  = ',rcntrl(4)
    1862           write(9,*) '    FacMax  = ',rcntrl(5)
    1863           write(9,*) ' '
    1864           IF(vl_dim > 1)    THEN
    1865              write(9,*) '    Vector mode                   vektor length = ',vl_dim
    1866           ELSE
    1867              write(9,*) '    Scalar mode'
    1868           ENDIF
    1869           write(9,*) ' '
    1870        END IF
     1867!        IF(myid == 0)   THEN
     1868!           write(9,*) ' '
     1869!           write(9,*) 'kpp setup '
     1870!           write(9,*) ' '
     1871!           write(9,*) '    gas_phase chemistry: solver_type = ',trim(solver_type)
     1872!           write(9,*) ' '
     1873!           write(9,*) '    Hstart  = ',rcntrl(3)
     1874!           write(9,*) '    FacMin  = ',rcntrl(4)
     1875!           write(9,*) '    FacMax  = ',rcntrl(5)
     1876!           write(9,*) ' '
     1877!           IF(vl_dim > 1)    THEN
     1878!              write(9,*) '    Vector mode                   vektor length = ',vl_dim
     1879!           ELSE
     1880!              write(9,*) '    Scalar mode'
     1881!           ENDIF
     1882!           write(9,*) ' '
     1883!        END IF
    18711884
    18721885       RETURN
Note: See TracChangeset for help on using the changeset viewer.