Ignore:
Timestamp:
Dec 4, 2018 8:40:18 AM (5 years ago)
Author:
maronga
Message:

revised calculation of near surface air potential temperature

File:
1 edited

Legend:

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

    r3547 r3597  
    2626! -----------------
    2727! $Id$
     28! Added routine for calculating near surface air potential temperature (moved
     29! from urban_surface_mod)
     30!
     31! 3547 2018-11-21 13:21:24Z suehring
    2832! variables documented
    2933!
     
    250254        ONLY:  air_chemistry, cloud_droplets,                                  &
    251255               constant_heatflux, constant_scalarflux,                         &
    252                constant_waterflux, coupling_mode, humidity, ibc_e_b,           &
    253                ibc_pt_b, initializing_actions,                                 &
     256               constant_waterflux, coupling_mode, do_output_at_2m, humidity,   &
     257               ibc_e_b, ibc_pt_b, indoor_model, initializing_actions,          &
    254258               intermediate_timestep_count, intermediate_timestep_count_max,   &
    255259               land_surface, large_scale_forcing, lsf_surf, message_string,    &
     
    413417             CALL calc_us
    414418             CALL calc_surface_fluxes
     419             
     420             IF ( do_output_at_2m )  THEN
     421                CALL calc_pt_near_surface ( '2m' )
     422             ENDIF
    415423          ENDIF
    416424!
     
    423431             CALL calc_us
    424432             CALL calc_surface_fluxes
     433             IF ( do_output_at_2m )  THEN
     434                CALL calc_pt_near_surface ( '2m' )
     435             ENDIF
    425436          ENDIF
    426437!
     
    433444             CALL calc_us
    434445             CALL calc_surface_fluxes
     446             IF ( do_output_at_2m )  THEN
     447                CALL calc_pt_near_surface ( '2m' )
     448             ENDIF
     449             IF ( indoor_model )  THEN
     450                CALL calc_pt_near_surface ( '10cm' )
     451             ENDIF
    435452          ENDIF
    436453!
     
    447464             CALL calc_scaling_parameters
    448465             CALL calc_surface_fluxes
     466             IF ( do_output_at_2m )  THEN
     467                CALL calc_pt_near_surface ( '2m' )
     468             ENDIF
    449469          ENDIF
    450470!
     
    457477             CALL calc_scaling_parameters
    458478             CALL calc_surface_fluxes
     479             IF ( do_output_at_2m )  THEN
     480                CALL calc_pt_near_surface ( '2m' )
     481             ENDIF
    459482          ENDIF
    460483!
     
    467490             CALL calc_scaling_parameters
    468491             CALL calc_surface_fluxes
     492             IF ( do_output_at_2m )  THEN
     493                CALL calc_pt_near_surface ( '2m' )
     494             ENDIF
     495             IF ( indoor_model )  THEN
     496                CALL calc_pt_near_surface ( '10cm' )
     497             ENDIF
    469498          ENDIF
    470499
     
    23052334    END SUBROUTINE calc_surface_fluxes
    23062335
     2336   
     2337!------------------------------------------------------------------------------!
     2338! Description:
     2339! ------------
     2340!> Calculates temperature near surface (10 cm) for indoor model or 2 m
     2341!> temperature for output
     2342!------------------------------------------------------------------------------!
     2343    SUBROUTINE calc_pt_near_surface ( z_char )
     2344
     2345       IMPLICIT NONE
     2346
     2347       CHARACTER (LEN = *), INTENT(IN)       :: z_char          !< string identifier to identify z level
     2348       INTEGER(iwp)                          :: i, j, k, l, m   !< running indices
     2349
     2350       
     2351       SELECT CASE ( z_char)
     2352           
     2353       
     2354          CASE ( '10cm' )
     2355
     2356             DO  m = 1, surf%ns
     2357
     2358                i = surf%i(m)
     2359                j = surf%j(m)
     2360                k = surf%k(m)
     2361
     2362                surf%pt_10cm(m) = surf%pt_surface(m) + surf%ts(m) / kappa  &
     2363                                   * ( log( 0.1_wp /  surf%z0h(m) )                    &
     2364                                  - psi_h( 0.1_wp / surf%ol(m) )                    &
     2365                                     + psi_h( surf%z0h(m) / surf%ol(m) ) )
     2366
     2367             ENDDO
     2368
     2369
     2370          CASE ( '2m' )
     2371     
     2372             DO  m = 1, surf%ns
     2373
     2374                i = surf%i(m)
     2375                j = surf%j(m)
     2376                k = surf%k(m)
     2377
     2378                surf%pt_2m(m) = surf%pt_surface(m) + surf%ts(m) / kappa  &
     2379                                   * ( log( 2.0_wp /  surf%z0h(m) )                    &
     2380                                     - psi_h( 2.0_wp / surf%ol(m) )                    &
     2381                                     + psi_h( surf%z0h(m) / surf%ol(m) ) )
     2382
     2383             ENDDO
     2384         
     2385       
     2386       END SELECT
     2387
     2388    END SUBROUTINE calc_pt_near_surface
     2389   
    23072390
    23082391!
Note: See TracChangeset for help on using the changeset viewer.