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_layer_fluxes_mod.f90

    r4298 r4331  
    2626! -----------------
    2727! $Id$
     28! Calculation of diagnostic-only 2-m potential temperature moved to
     29! diagnostic_output_quantities.
     30!
     31! 4298 2019-11-21 15:59:16Z suehring
    2832! Calculation of 2-m temperature adjusted to the case the 2-m level is above
    2933! the first grid point.
     
    108112               constant_waterflux, coupling_mode,                              &
    109113               debug_output_timestep,                                          &
    110                do_output_at_2m, humidity,                                      &
     114               humidity,                                                       &
    111115               ibc_e_b, ibc_pt_b, indoor_model,                                &
    112116               land_surface, large_scale_forcing, lsf_surf, message_string,    &
     
    162166    PRIVATE
    163167
    164     PUBLIC init_surface_layer_fluxes, phi_m, surface_layer_fluxes
     168    PUBLIC init_surface_layer_fluxes,                                          &
     169           phi_m,                                                              &
     170           psi_h,                                                              &
     171           psi_m,                                                              &
     172           surface_layer_fluxes
    165173
    166174    INTERFACE init_surface_layer_fluxes
     
    171179       MODULE PROCEDURE phi_m
    172180    END INTERFACE phi_m
     181
     182    INTERFACE psi_h
     183       MODULE PROCEDURE psi_h
     184    END INTERFACE psi_h
     185
     186    INTERFACE psi_m
     187       MODULE PROCEDURE psi_m
     188    END INTERFACE psi_m
    173189
    174190    INTERFACE surface_layer_fluxes
     
    259275          CALL calc_scaling_parameters
    260276          CALL calc_surface_fluxes
    261           IF ( do_output_at_2m )  THEN
    262              CALL calc_pt_near_surface ( '2m' )
    263           ENDIF
    264277       ENDIF
    265278!
     
    272285          CALL calc_scaling_parameters
    273286          CALL calc_surface_fluxes
    274           IF ( do_output_at_2m )  THEN
    275              CALL calc_pt_near_surface ( '2m' )
    276           ENDIF
    277287       ENDIF
    278288!
     
    285295          CALL calc_scaling_parameters
    286296          CALL calc_surface_fluxes
    287           IF ( do_output_at_2m )  THEN
    288              CALL calc_pt_near_surface ( '2m' )
    289           ENDIF
    290297!
    291298!--       Calculate 10cm temperature, required in indoor model
     
    18631870       INTEGER(iwp)                    :: j      !< grid index y-dimension
    18641871       INTEGER(iwp)                    :: k      !< grid index z-dimension
    1865        INTEGER(iwp)                    :: kk     !< running index along the z-dimension
    18661872       INTEGER(iwp)                    :: m      !< running index for surface elements
    18671873
     
    18821888                                     - psi_h( 0.1_wp / surf%ol(m) )            &
    18831889                                     + psi_h( surf%z0h(m) / surf%ol(m) ) )
    1884                                    
    1885              ENDDO
    1886 
    1887 !
    1888 !--       2-m temperature. Note, this is only calculated for output reasons at
    1889 !--       horizontal upward-facing surfaces.
    1890           CASE ( '2m' )
    1891      
    1892              DO  m = 1, surf%ns
    1893 
    1894                 i = surf%i(m)
    1895                 j = surf%j(m)
    1896                 k = surf%k(m)
    1897 !
    1898 !--             If 2-m level is below the first grid level, MOST is
    1899 !--             used for calculation of 2-m temperature.
    1900                 IF ( surf%z_mo(m) > 2.0_wp )  THEN
    1901                    surf%pt_2m(m) = surf%pt_surface(m) + surf%ts(m) / kappa     &
    1902                                    * ( LOG( 2.0_wp /  surf%z0h(m) )            &
    1903                                      - psi_h( 2.0_wp / surf%ol(m) )            &
    1904                                      + psi_h( surf%z0h(m) / surf%ol(m) ) )
    1905 !
    1906 !--             If 2-m level is above the first grid level, 2-m temperature
    1907 !--             is linearly interpolated between the two nearest vertical grid
    1908 !--             levels. Note, since 2-m temperature is only computed for
    1909 !--             horizontal upward-facing surfaces, only a vertical
    1910 !--             interpolation is necessary.
    1911                 ELSE
    1912 !
    1913 !--                zw(k-1) defines the height of the surface.
    1914                    kk = k
    1915                    DO WHILE ( zu(kk) - zw(k-1) < 2.0_wp  .AND.  kk <= nzt )
    1916                       kk = kk + 1
    1917                    ENDDO               
    1918 !
    1919 !--                kk defines the index of the first grid level >= 2m.
    1920                    surf%pt_2m(m) = pt(kk-1,j,i) +                              &
    1921                                  ( zw(k-1) + 2.0_wp - zu(kk-1)     ) *         &
    1922                                  ( pt(kk,j,i)       - pt(kk-1,j,i) ) /         &
    1923                                  ( zu(kk)           - zu(kk-1)     )
    1924                 ENDIF
    1925 
    1926              ENDDO
    1927          
    1928        
     1890
     1891             ENDDO
     1892
    19291893       END SELECT
    19301894
Note: See TracChangeset for help on using the changeset viewer.