Changeset 1697


Ignore:
Timestamp:
Oct 28, 2015 5:14:10 PM (8 years ago)
Author:
raasch
Message:

FORTRAN an OpenMP errors removed
misplaced cpp-directive fixed
small E- and F-FORMAT changes to avoid informative compiler messages about insufficient field width

Location:
palm/trunk/SOURCE
Files:
6 edited

Legend:

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

    r1692 r1697  
    1919! Current revisions:
    2020! -----------------
    21 !
     21! small E- and F-FORMAT changes to avoid informative compiler messages about
     22! insufficient field width
    2223!
    2324! Former revisions:
     
    853854
    854855!--       Building output strings, starting with surface value
    855           WRITE ( leaf_area_density, '(F6.4)' )  lad_surface
     856          WRITE ( leaf_area_density, '(F7.4)' )  lad_surface
    856857          gradients = '------'
    857858          slices = '     0'
     
    880881       ELSE
    881882       
    882           WRITE ( leaf_area_density, '(F6.4)' )  lad_surface
     883          WRITE ( leaf_area_density, '(F7.4)' )  lad_surface
    883884          coordinates = '   0.0'
    884885         
     
    19251926111 FORMAT (' --> Solve perturbation pressure via FFT using ',A,' routines')
    19261927112 FORMAT (' --> Solve perturbation pressure via SOR-Red/Black-Schema'/ &
    1927             '     Iterations (initial/other): ',I3,'/',I3,'  omega = ',F5.3)
     1928            '     Iterations (initial/other): ',I3,'/',I3,'  omega =',F6.3)
    19281929113 FORMAT (' --> Momentum advection via Piascek-Williams-Scheme (Form C3)', &
    19291930                  ' or Upstream')
     
    19381939122 FORMAT (' --> Time differencing scheme: ',A)
    19391940123 FORMAT (' --> Rayleigh-Damping active, starts ',A,' z = ',F8.2,' m'/ &
    1940             '     maximum damping coefficient: ',F5.3, ' 1/s')
     1941            '     maximum damping coefficient:',F6.3, ' 1/s')
    19411942129 FORMAT (' --> Additional prognostic equation for the specific humidity')
    19421943130 FORMAT (' --> Additional prognostic equation for the total water content')
     
    19931994             ' ----------------------------------'/)
    19941995201 FORMAT ( ' Timestep:             variable     maximum value: ',F6.3,' s', &
    1995              '    CFL-factor: ',F4.2)
     1996             '    CFL-factor:',F5.2)
    19961997202 FORMAT ( ' Timestep:          dt = ',F6.3,' s'/)
    19971998203 FORMAT ( ' Start time:          ',F9.3,' s'/ &
     
    20122013              ' m  z(u) = ',F10.3,' m'/)
    20132014252 FORMAT (' dz constant up to ',F10.3,' m (k=',I4,'), then stretched by', &
    2014               ' factor: ',F5.3/ &
     2015              ' factor:',F6.3/ &
    20152016            ' maximum dz not to be exceeded is dz_max = ',F10.3,' m'/)
    20162017254 FORMAT (' Number of gridpoints (x,y,z):  (0:',I4,', 0:',I4,', 0:',I4,')'/ &
     
    20662067305 FORMAT (//'    Prandtl-Layer between bottom surface and first ', &
    20672068               'computational u,v-level:'// &
    2068              '       zp = ',F6.2,' m   z0 = ',F6.4,' m   z0h = ',F7.5,&
    2069              ' m   kappa = ',F4.2/ &
    2070              '       Rif value range:   ',F6.2,' <= rif <=',F6.2)
     2069             '       zp = ',F6.2,' m   z0 =',F7.4,' m   z0h =',F8.5,&
     2070             ' m   kappa =',F5.2/ &
     2071             '       Rif value range:   ',F8.2,' <= rif <=',F6.2)
    20712072306 FORMAT ('       Predefined constant heatflux:   ',F9.6,' K m/s')
    20722073307 FORMAT ('       Heatflux has a random normal distribution')
     
    20872088318 FORMAT (/'       use_cmax: ',L1 / &
    20882089            '       pt damping layer width = ',F8.2,' m, pt ', &
    2089                     'damping factor = ',F6.4)
     2090                    'damping factor =',F7.4)
    20902091319 FORMAT ('       turbulence recycling at inflow switched on'/ &
    20912092            '       width of recycling domain: ',F7.1,' m   grid index: ',I4/ &
     
    22032204              ' -------------------'/)
    22042205410 FORMAT ('    Geograph. latitude  :   phi    = ',F4.1,' degr'/   &
    2205             '    Angular velocity    :   omega  = ',E9.3,' rad/s'/  &
     2206            '    Angular velocity    :   omega  =',E10.3,' rad/s'/  &
    22062207            '    Coriolis parameter  :   f      = ',F9.6,' 1/s'/    &
    22072208            '                            f*     = ',F9.6,' 1/s')
     
    22142215416 FORMAT ('    Surface pressure   :   p_0   = ',F7.2,' hPa'/      &
    22152216            '    Gas constant       :   R     = ',F5.1,' J/(kg K)'/ &
    2216             '    Density of air     :   rho_0 = ',F5.3,' kg/m**3'/  &
     2217            '    Density of air     :   rho_0 =',F6.3,' kg/m**3'/  &
    22172218            '    Specific heat cap. :   c_p   = ',F6.1,' J/(kg K)'/ &
    2218             '    Vapourization heat :   L_v   = ',E8.2,' J/kg')
     2219            '    Vapourization heat :   L_v   =',E9.2,' J/kg')
    22192220417 FORMAT ('    Geograph. longitude :   lambda = ',F4.1,' degr')
    22202221418 FORMAT (/'    Day of the year at model start :   day_init      =     ',I3 &
     
    22982299                   ' default)')
    22992300447 FORMAT (' --> RRTMG scheme is used')
    2300 448 FORMAT (/'     User-specific surface albedo: albedo = ', F5.3)
     2301448 FORMAT (/'     User-specific surface albedo: albedo =', F6.3)
    23012302449 FORMAT  ('     Timestep: dt_radiation = ', F5.2, '  s')
    23022303
     
    23052306451 FORMAT ('    Diffusion coefficients are constant:'/ &
    23062307            '    Km = ',F6.2,' m**2/s   Kh = ',F6.2,' m**2/s   Pr = ',F5.2)
    2307 453 FORMAT ('    Mixing length is limited to ',F4.2,' * z')
     2308453 FORMAT ('    Mixing length is limited to',F5.2,' * z')
    23082309454 FORMAT ('    TKE is not allowed to fall below ',E9.2,' (m/s)**2')
    23092310455 FORMAT ('    initial TKE is prescribed as ',E9.2,' (m/s)**2')
     
    23152316              ' -----------------------------'/)
    23162317471 FORMAT ('    Disturbance impulse (u,v) every :   ',F6.2,' s'/            &
    2317             '    Disturbance amplitude           :     ',F4.2, ' m/s'/       &
     2318            '    Disturbance amplitude           :    ',F5.2, ' m/s'/       &
    23182319            '    Lower disturbance level         : ',F8.2,' m (GP ',I4,')'/  &
    23192320            '    Upper disturbance level         : ',F8.2,' m (GP ',I4,')')
     
    23212322                 ' to i/j =',I4)
    23222323473 FORMAT ('    Disturbances cease as soon as the disturbance energy exceeds',&
    2323                  1X,F5.3, ' m**2/s**2')
     2324                 F6.3, ' m**2/s**2')
    23242325474 FORMAT ('    Random number generator used    : ',A/)
    23252326475 FORMAT ('    The surface temperature is increased (or decreased, ', &
     
    23542355487 FORMAT ('       Number of particle groups: ',I2/)
    23552356488 FORMAT ('       SGS velocity components are used for particle advection'/ &
    2356             '          minimum timestep for advection: ', F7.5/)
     2357            '          minimum timestep for advection:', F8.5/)
    23572358489 FORMAT ('       Number of particles simultaneously released at each ', &
    23582359                    'point: ', I5/)
     
    23602361            '          Particle radius: ',E10.3, 'm')
    23612362491 FORMAT ('          Particle inertia is activated'/ &
    2362             '             density_ratio (rho_fluid/rho_particle) = ',F5.3/)
     2363            '             density_ratio (rho_fluid/rho_particle) =',F6.3/)
    23632364492 FORMAT ('          Particles are advected only passively (no inertia)'/)
    23642365493 FORMAT ('          Boundaries of particle source: x:',F8.1,' - ',F8.1,' m'/&
     
    23892390510 FORMAT ('    Droplet density    :   N_c   = ',F6.1,' 1/cm**3')
    23902391511 FORMAT ('    Sedimentation Courant number:                  '/&
    2391             '                               C_s   = ',F3.1,'        ')
     2392            '                               C_s   =',F4.1,'        ')
    23922393512 FORMAT (/' Date:                 ',A8,6X,'Run:       ',A20/      &
    23932394            ' Time:                 ',A8,6X,'Run-No.:   ',I2.2/     &
  • palm/trunk/SOURCE/init_1d_model.f90

    r1692 r1697  
    1919! Current revisions:
    2020! -----------------
    21 !
     21! small E- and F-FORMAT changes to avoid informative compiler messages about
     22! insufficient field width
    2223!
    2324! Former revisions:
     
    831832           &'ITER.  HH:MM:SS    DT      UMAX   VMAX    U*   ALPHA   ENERG.'/ &
    832833           &'-------------------------------------------------------------')
    833 101 FORMAT (I5,2X,A9,1X,F6.2,2X,F6.2,1X,F6.2,2X,F5.3,2X,F5.1,2X,F7.2)
     834101 FORMAT (I5,2X,A9,1X,F6.2,2X,F6.2,1X,F6.2,1X,F6.3,2X,F5.1,2X,F7.2)
    834835
    835836
  • palm/trunk/SOURCE/land_surface_model.f90

    r1696 r1697  
    1919! Current revisions:
    2020! -----------------
    21 !
     21! bugfix: misplaced cpp-directive
    2222!
    2323! Former revisions:
     
    13741374       ENDDO
    13751375
    1376 #if defined( __parallel )
    13771376!
    13781377!--    Make a logical OR for all processes. Force radiation call if at
    13791378!--    least one processor
    1380        IF ( intermediate_timestep_count == intermediate_timestep_count_max-1 )&
     1379       IF ( intermediate_timestep_count == intermediate_timestep_count_max-1 ) &
    13811380       THEN
    1382 
     1381#if defined( __parallel )
    13831382          IF ( collective_wait )  CALL MPI_BARRIER( comm2d, ierr )
    13841383          CALL MPI_ALLREDUCE( force_radiation_call_l, force_radiation_call,    &
  • palm/trunk/SOURCE/print_1d.f90

    r1683 r1697  
    1919! Current revisions:
    2020! -----------------
    21 !
     21! small E- and F-FORMAT changes to avoid informative compiler messages about
     22! insufficient field width
    2223!
    2324! Former revisions:
     
    175176112 FORMAT (/)
    176177120 FORMAT ('   k     zu      u     du     v     dv     pt    dpt    ', &
    177             'e      Km    Kh     l      zu      k')
     178            ' e      Km    Kh     l      zu      k')
    178179121 FORMAT (1X,I4,1X,F7.1,1X,F6.2,1X,F5.2,1X,F6.2,1X,F5.2,2X,F6.2,1X,F5.2, &
    179             1X,F6.4,1X,F5.2,1X,F5.2,1X,F6.2,1X,F7.1,2X,I4)
    180 130 FORMAT ('   k     zw      w''pt''     wpt       w''u''      wu       ', &
    181             ' w''v''      wv        zw      k')
    182 131 FORMAT (1X,I4,1X,F7.1,6(1X,E9.3),1X,F7.1,2X,I4)
     180            1X,F7.4,1X,F5.2,1X,F5.2,1X,F6.2,1X,F7.1,2X,I4)
     181130 FORMAT ('   k     zw       w''pt''      wpt        w''u''       wu       ',&
     182            '  w''v''       wv        zw      k')
     183131 FORMAT (1X,I4,1X,F7.1,6(1X,E10.3),1X,F7.1,2X,I4)
    183184
    184185
  • palm/trunk/SOURCE/run_control.f90

    r1683 r1697  
    1919! Current revisions:
    2020! -----------------
    21 !
     21! small E- and F-FORMAT changes to avoid informative compiler messages about
     22! insufficient field width
    2223!
    2324! Former revisions:
     
    119120       ENDIF
    120121       WRITE ( 15, 101 )  runnr, current_timestep_number, simulated_time_chr,  &
    121                           simulated_time-INT( simulated_time ), dt_3d,         &
    122                           timestep_reason, u_max, disturb_chr,                 &
     122                          INT( ( simulated_time-INT( simulated_time ) ) * 100),&
     123                          dt_3d, timestep_reason, u_max, disturb_chr,          &
    123124                          v_max, disturb_chr, w_max, hom(nzb,1,pr_palm,0),     &
    124125                          hom(nzb+8,1,pr_palm,0), hom(nzb+3,1,pr_palm,0),      &
     
    153154          &'----------------------------------------------------------------', &
    154155          &'---------')
    155 101 FORMAT (I3,1X,I6,1X,A8,F3.2,1X,F8.4,A1,1X,F8.4,A1,F8.4,A1,F8.4,2X,F5.3,2X, &
    156             F4.2, &
     156101 FORMAT (I3,1X,I6,1X,A8,'.',I2.2,1X,F8.4,A1,1X,F8.4,A1,F8.4,A1,F8.4,1X,    &
     157            F6.3,1X,F5.2, &
    157158            2X,E10.3,2X,F6.0,1X,4(E10.3,1X),3(3(I4),1X),F8.3,1X,F8.3,5X,I3)
    158159
  • palm/trunk/SOURCE/surface_layer_fluxes.f90

    • Property svn:keywords set to Id
    r1692 r1697  
    1919! Current revisions:
    2020! -----------------
    21 !
     21! FORTRAN and OpenMP errors removed
    2222!
    2323! Former revisions:
     
    2525! $Id$
    2626!
    27 !
     27! 1696 2015-10-27 10:03:34Z maronga
    2828! Modularized and completely re-written version of prandtl_fluxes.f90. In the
    2929! course of the re-writing two additional methods have been implemented. See
     
    9090!>    that this method cannot be used in case of roughness heterogeneity
    9191!>
    92 !> @todo limiting of uv_total might be required is some cases
     92!> @todo limiting of uv_total might be required in some cases
    9393!> @todo (re)move large_scale_forcing actions
    9494!> @todo check/optimize OpenMP and OpenACC directives
     
    387387                       l        !< look index
    388388
    389        REAL(wp), DIMENSION(nysg:nyng,nxlg:nxrg) :: rib                
     389       REAL(wp), DIMENSION(nysg:nyng,nxlg:nxrg) :: rib !< Bulk Richardson number
    390390                       
    391391       REAL(wp)     :: f,      & !< Function for Newton iteration: f = Ri - [...]/[...]^2 = 0
     
    394394                       ol_m,   & !< Previous value of L for Newton iteration
    395395                       ol_old, & !< Previous time step value of L
    396                        ol_u,   & !< Upper bound of L for Newton iteration
    397                        rib       !< Bulk Richardson number
     396                       ol_u      !< Upper bound of L for Newton iteration
    398397
    399398!
     
    686685       IMPLICIT NONE
    687686
     687       !$OMP PARALLEL DO PRIVATE( k, z_mo )
     688       !$acc kernels loop
    688689       DO  i = nxlg, nxrg
    689690          DO  j = nysg, nyng
     
    694695!
    695696!--          Compute u* at the scalars' grid points
    696              !$OMP PARALLEL DO PRIVATE( a, b, k, uv_total, z_mo )
    697              !$acc kernels loop
    698697             us(j,i) = kappa * uv_total(j,i) / ( LOG( z_mo / z0(j,i) )         &
    699698                                          - psi_m( z_mo / ol(j,i) )            &
     
    764763          ENDIF
    765764
    766           !$OMP PARALLEL DO PRIVATE( a, b, k, z_mo )
     765          !$OMP PARALLEL DO PRIVATE( k, z_mo )
    767766          !$acc kernels loop
    768767          DO  i = nxlg, nxrg
     
    817816             ENDIF
    818817
    819              !$OMP PARALLEL DO PRIVATE( a, b, k, z_mo )
     818             !$OMP PARALLEL DO PRIVATE( e_s, k, z_mo )
    820819             !$acc kernels loop independent
    821820             DO  i = nxlg, nxrg
     
    859858       IF ( cloud_physics .AND. icloud_scheme == 0 .AND. precipitation )  THEN
    860859
    861           !$OMP PARALLEL DO PRIVATE( a, b, k, z_mo )
     860          !$OMP PARALLEL DO PRIVATE( k, z_mo )
    862861          !$acc kernels loop independent
    863862          DO  i = nxlg, nxrg
Note: See TracChangeset for help on using the changeset viewer.