Ignore:
Timestamp:
Mar 19, 2007 8:20:46 AM (17 years ago)
Author:
raasch
Message:

preliminary changes for precipitation output

File:
1 edited

Legend:

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

    r63 r72  
    66! "by_user" allowed as initializing action, -data_output_ts,
    77! leapfrog with non-flat topography not allowed any more, loop_optimization
    8 ! and pt_reference are checked
     8! and pt_reference are checked,
     9! output of precipitation amount/rate and roughnes length + check
     10! possible negative humidities are avoided in initial profile
    911!
    1012! Former revisions:
     
    351353
    352354    IF ( cloud_physics  .AND.  .NOT. moisture )  THEN
    353        IF ( myid == 0 )  PRINT*, '+++ check_parameters: moisture =', &
    354                                  moisture, ' is not allowed with ',  &
    355                                  'cloud_physics=', cloud_physics
     355       IF ( myid == 0 )  PRINT*, '+++ check_parameters: cloud_physics =', &
     356                                 cloud_physics, ' is not allowed with ',  &
     357                                 'moisture =', moisture
     358       CALL local_stop
     359    ENDIF
     360
     361    IF ( precipitation  .AND.  .NOT.  cloud_physics )  THEN
     362       IF ( myid == 0 )  PRINT*, '+++ check_parameters: precipitation =', &
     363                                 precipitation, ' is not allowed with ',  &
     364                                 'cloud_physics =', cloud_physics
    356365       CALL local_stop
    357366    ENDIF
     
    570579                q_init(k) = q_init(k-1)
    571580             ENDIF
     581!
     582!--          Avoid negative humidities
     583             IF ( q_init(k) < 0.0 )  THEN
     584                q_init(k) = 0.0
     585             ENDIF
    572586          ENDDO
    573587
     
    11631177
    11641178!
     1179!-- Set the default value for the integration interval of precipitation amount
     1180    IF ( precipitation )  THEN
     1181       IF ( precipitation_amount_interval == 9999999.9 )  THEN
     1182          precipitation_amount_interval = dt_do2d_xy
     1183       ELSE
     1184          IF ( precipitation_amount_interval > dt_do2d_xy )  THEN
     1185             IF ( myid == 0 )  PRINT*, '+++ check_parameters: ',              &
     1186                                       'precipitation_amount_interval =',     &
     1187                                        precipitation_amount_interval,        &
     1188                                       ' must not be larger than dt_do2d_xy', &
     1189                                       ' = ', dt_do2d_xy   
     1190       CALL local_stop
     1191          ENDIF
     1192       ENDIF
     1193    ENDIF
     1194
     1195!
    11651196!-- Determine the number of output profiles and check whether they are
    11661197!-- permissible
     
    18401871             unit = 'conc'
    18411872
    1842           CASE ( 'u*', 't*', 'lwp*' )
     1873          CASE ( 'u*', 't*', 'lwp*', 'pra*', 'prr*', 'z0*' )
    18431874             IF ( k == 0  .OR.  data_output(i)(ilen-2:ilen) /= '_xy' )  THEN
    18441875                IF ( myid == 0 )  THEN
     
    18561887                CALL local_stop
    18571888             ENDIF
     1889             IF ( TRIM( var ) == 'pra*'  .AND.  .NOT. precipitation )  THEN
     1890                IF ( myid == 0 )  THEN
     1891                   PRINT*, '+++ check_parameters: output of "', TRIM( var ), &
     1892                                '" requires precipitation = .TRUE.'
     1893                ENDIF
     1894                CALL local_stop
     1895             ENDIF
     1896             IF ( TRIM( var ) == 'pra*'  .AND.  j == 1 )  THEN
     1897                IF ( myid == 0 )  THEN
     1898                   PRINT*, '+++ check_parameters: temporal averaging of ', &
     1899                           ' precipitation amount "', TRIM( var ),         &
     1900                           '" not possible'
     1901                ENDIF
     1902                CALL local_stop
     1903             ENDIF
     1904             IF ( TRIM( var ) == 'prr*'  .AND.  .NOT. precipitation )  THEN
     1905                IF ( myid == 0 )  THEN
     1906                   PRINT*, '+++ check_parameters: output of "', TRIM( var ), &
     1907                                '" requires precipitation = .TRUE.'
     1908                ENDIF
     1909                CALL local_stop
     1910             ENDIF
     1911
     1912
    18581913             IF ( TRIM( var ) == 'u*'   )  unit = 'm/s'
    18591914             IF ( TRIM( var ) == 't*'   )  unit = 'K'
    18601915             IF ( TRIM( var ) == 'lwp*' )  unit = 'kg/kg*m'
     1916             IF ( TRIM( var ) == 'pra*' )  unit = 'mm'
     1917             IF ( TRIM( var ) == 'prr*' )  unit = 'mm/s'
     1918             IF ( TRIM( var ) == 'z0*'  )  unit = 'm'
    18611919
    18621920          CASE ( 'p', 'pt', 'u', 'v', 'w' )
Note: See TracChangeset for help on using the changeset viewer.