Ignore:
Timestamp:
Dec 10, 2019 6:25:02 PM (5 years ago)
Author:
suehring
Message:

New diagnostic output for 10-m wind speed; Diagnostic output of 2-m potential temperature moved to diagnostic output

File:
1 edited

Legend:

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

    r4329 r4331  
    2626! -----------------
    2727! $Id$
     28! -pt_2m - array is moved to diagnostic_output_quantities
     29!
     30! 4329 2019-12-10 15:46:36Z motisi
    2831! Renamed wall_flags_0 to wall_flags_static_0
    2932!
     
    289292       
    290293       REAL(wp), DIMENSION(:), ALLOCATABLE ::  pt_10cm             !< near surface air potential temperature at distance 10 cm from the surface (K)
    291        REAL(wp), DIMENSION(:), ALLOCATABLE ::  pt_2m               !< near surface air potential temperature at distance 2 m from the surface (K)     
    292294       
    293295       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  alpha_vg          !< coef. of Van Genuchten
     
    12811283!--    Salinity surface flux
    12821284       IF ( ocean_mode )  DEALLOCATE ( surfaces%sasws )
    1283 !
    1284 !--    2-m potential temperature (for output quantity theta_2m*)
    1285        IF ( do_output_at_2m )  DEALLOCATE ( surfaces%pt_2m )
    12861285
    12871286    END SUBROUTINE deallocate_surface_attributes_h
     
    14121411!--    Salinity surface flux
    14131412       IF ( ocean_mode )  ALLOCATE ( surfaces%sasws(1:surfaces%ns) )
    1414 !
    1415 !--    2-m potential temperature (for output quantity theta_2m*)
    1416        IF ( do_output_at_2m )  THEN
    1417           ALLOCATE ( surfaces%pt_2m(1:surfaces%ns) )
    1418           surfaces%pt_2m = -9999.0_wp  !< output array (for theta_2m*) must be initialized here,
    1419                                        !< otherwise simulation crash at do2d_at_begin with spinup=.F.
    1420        ENDIF
    14211413
    14221414    END SUBROUTINE allocate_surface_attributes_h
Note: See TracChangeset for help on using the changeset viewer.