Ignore:
Timestamp:
Oct 19, 2018 12:34:59 PM (6 years ago)
Author:
kanani
Message:

merge fixes of radiation branch (r3362) to trunk

File:
1 edited

Legend:

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

    r3371 r3378  
    2828! -----------------
    2929! $Id$
     30! merge from radiation branch (r3362) into trunk
     31! (moh.hefny):
     32! - check the requested output variables if they are correct
     33! - added unscheduled_radiation_calls switch to control force_radiation_call
     34! - minor formate changes
     35!
     36! 3371 2018-10-18 13:40:12Z knoop
    3037! Set flag indicating that albedo at urban surfaces is already initialized
    3138!
     
    399406               idcsf, ndcsf, kdcsf, pct,                                       &
    400407               startland, endland, startwall, endwall, skyvf, skyvft, nzub,    &
    401                nzut, nzpt, npcbl, pcbl
     408               nzut, npcbl, pcbl, unscheduled_radiation_calls
    402409
    403410    USE statistics,                                                            &
     
    23992406        IMPLICIT NONE
    24002407 
    2401         CHARACTER (len=*),INTENT(IN)    ::  variable !:
    2402         CHARACTER (len=*),INTENT(OUT)   ::  unit     !:
    2403        
    2404         CHARACTER (len=varnamelength)   :: var
    2405 
     2408        CHARACTER(LEN=*),INTENT(IN)    ::  variable !:
     2409        CHARACTER(LEN=*),INTENT(OUT)   ::  unit     !:
     2410
     2411        INTEGER(iwp)                                  :: i,j          !< index
     2412        CHARACTER(LEN=varnamelength)                  :: var
     2413        INTEGER(iwp), PARAMETER                       :: nl1 = 32     !< number of directional usm variables
     2414        CHARACTER(LEN=varnamelength), DIMENSION(nl1)  :: varlist1 = & !< list of directional usm variables
     2415                  (/'usm_rad_net','usm_rad_insw','usm_rad_inlw','usm_rad_inswdir',     &
     2416                    'usm_rad_inswdif','usm_rad_inswref','usm_rad_inlwdif','usm_wshf',  &
     2417                    'usm_rad_inlwref','usm_rad_outsw','usm_rad_outlw','usm_rad_hf',    &
     2418                    'usm_rad_ressw','usm_rad_reslw','usm_wghf','usm_wghf_window',      &
     2419                    'usm_wghf_green','usm_iwghf','usm_iwghf_window','usm_surfz',       &
     2420                    'usm_surfwintrans','usm_surfcat','usm_surfalb','usm_surfemis',     &
     2421                    'usm_t_surf','usm_t_surf_window','usm_t_surf_green','usm_t_green', &
     2422                    'usm_t_surf_10cm','usm_t_wall','usm_t_window','usm_t_green'/)
     2423
     2424        INTEGER(iwp), PARAMETER                       :: nl2 = 9      !< number of other variables
     2425        CHARACTER(LEN=varnamelength), DIMENSION(nl2)  :: varlist2 = & !< list of other usm variables
     2426                  (/'usm_skyvf','usm_skyvft','usm_svf','usm_dif','usm_rad_pc_inlw',    &
     2427                  'usm_rad_pc_insw','usm_rad_pc_inswdir','usm_rad_pc_inswdif',         &
     2428                  'usm_rad_pc_inswref'/)
     2429
     2430        INTEGER(iwp), PARAMETER                       :: nd = 5     !< number of directions
     2431        CHARACTER(LEN=6), DIMENSION(nd), PARAMETER  :: dirname = &  !< direction names
     2432                  (/'_roof ','_south','_north','_west ','_east '/)
     2433        LOGICAL                                       :: lfound     !< flag if the variable is found
     2434
     2435
     2436        lfound = .FALSE.
    24062437        var = TRIM(variable)
     2438
     2439!--     check if variable exists
     2440!       directional variables
     2441        DO i = 1, nl1
     2442           DO j = 1, nd
     2443              IF ( TRIM(var) == TRIM(varlist1(i))//TRIM(dirname(j)) ) THEN
     2444                 lfound = .TRUE.
     2445                 EXIT
     2446              ENDIF
     2447              IF ( lfound ) EXIT
     2448           ENDDO
     2449        ENDDO
     2450        IF ( lfound ) GOTO 10
     2451!       other variables
     2452        DO i = 1, nl2
     2453           IF ( TRIM(var) == TRIM(varlist2(i)) ) THEN
     2454              lfound = .TRUE.
     2455              EXIT
     2456           ENDIF
     2457        ENDDO
     2458        IF ( .NOT.  lfound ) THEN
     2459           unit = 'illegal'
     2460           RETURN
     2461        ENDIF
     246210      CONTINUE
     2463
     2464!--     check if variable exists
    24072465        IF ( var(1:12) == 'usm_rad_net_'  .OR.  var(1:13) == 'usm_rad_insw_'  .OR.        &
    24082466             var(1:13) == 'usm_rad_inlw_'  .OR.  var(1:16) == 'usm_rad_inswdir_'  .OR.    &
     
    25932651
    25942652          CASE ( 'usm_surfz' )
    2595 !--           array of lw radiation falling to local surface after i-th reflection
     2653!--           array of surface height (z)
    25962654              IF ( idsint == iup_u )  THEN
    25972655                 DO  m = 1, surf_usm_h%ns
     
    53325390              ENDIF
    53335391           ENDDO
    5334 !!!!!!!!!!!!!HACK!!!!!!!!!!!!!!!!!!!
    5335 !           t_window_v_p(l)%t = t_wall_v_p(l)%t
    5336 !           surf_usm_v(l)%tt_window_m  = surf_usm_v(l)%tt_wall_m
    5337 !           t_green_v_p(l)%t = t_wall_v_p(l)%t
    5338 !           surf_usm_v(l)%tt_green_m  = surf_usm_v(l)%tt_wall_m
    5339 !!!!!!!!!!!!!HACK!!!!!!!!!!!!!!!!!!!
    53405392        ENDDO
    53415393
     
    69146966        INTEGER(iwp)                                          :: wtc
    69156967        REAL(wp), DIMENSION(n_surface_params)                 :: wtp
    6916        
    69176968        LOGICAL                                               :: ascii_file = .FALSE.
    6918    
    69196969        INTEGER(iwp), DIMENSION(0:17, nysg:nyng, nxlg:nxrg)   :: usm_par
    69206970        REAL(wp), DIMENSION(1:14, nysg:nyng, nxlg:nxrg)       :: usm_val
     
    77427792!--        in case of fast changes in the skin temperature, it is required to
    77437793!--        update the radiative fluxes in order to keep the solution stable
    7744            IF ( ( ABS( t_surf_h_p(m) - t_surf_h(m) ) > 1.0_wp ) .OR. &
     7794           IF ( ( ( ABS( t_surf_h_p(m) - t_surf_h(m) ) > 1.0_wp ) .OR.          &
    77457795                ( ABS( t_surf_green_h_p(m) - t_surf_green_h(m) ) > 1.0_wp ) .OR. &
    7746                 ( ABS( t_surf_window_h_p(m) - t_surf_window_h(m) ) > 1.0_wp ) ) THEN
     7796                ( ABS( t_surf_window_h_p(m) - t_surf_window_h(m) ) > 1.0_wp ) )  &
     7797                 .AND.  unscheduled_radiation_calls  ) THEN
    77477798              force_radiation_call_l = .TRUE.
    77487799           ENDIF
     
    78977948
    78987949!--           add RK3 term
    7899               t_surf_v_p(l)%t(m) = t_surf_v_p(l)%t(m) + dt_3d * tsc(3) *       &
     7950              t_surf_v_p(l)%t(m) = t_surf_v_p(l)%t(m) + dt_3d * tsc(3) *                   &
    79007951                                surf_usm_v(l)%tt_surface_m(m)
    79017952              t_surf_window_v_p(l)%t(m) = t_surf_window_v_p(l)%t(m) + dt_3d * tsc(3) *     &
     
    79077958!--           store also vpt_surface, which is, due to the lack of moisture on roofs simply
    79087959!--           assumed to be the surface temperature.     
    7909               surf_usm_v(l)%pt_surface(m) =  ( surf_usm_v(l)%frac(ind_veg_wall,m) * t_surf_v_p(l)%t(m)  &
    7910                                       + surf_usm_v(l)%frac(ind_wat_win,m) * t_surf_window_v_p(l)%t(m)  &
     7960              surf_usm_v(l)%pt_surface(m) =  ( surf_usm_v(l)%frac(ind_veg_wall,m) * t_surf_v_p(l)%t(m)   &
     7961                                      + surf_usm_v(l)%frac(ind_wat_win,m) * t_surf_window_v_p(l)%t(m)    &
    79117962                                      + surf_usm_v(l)%frac(ind_pav_green,m) * t_surf_green_v_p(l)%t(m) ) &
    79127963                                      / exner(k)
     
    79207971              stend_window = ( t_surf_window_v_p(l)%t(m) - t_surf_window_v(l)%t(m) - dt_3d * tsc(3) *&
    79217972                        surf_usm_v(l)%tt_surface_window_m(m) ) / ( dt_3d  * tsc(2) )
    7922               stend_green = ( t_surf_green_v_p(l)%t(m) - t_surf_green_v(l)%t(m) - dt_3d * tsc(3) *&
     7973              stend_green = ( t_surf_green_v_p(l)%t(m) - t_surf_green_v(l)%t(m) - dt_3d * tsc(3) *   &
    79237974                        surf_usm_v(l)%tt_surface_green_m(m) ) / ( dt_3d  * tsc(2) )
    79247975
     
    79297980                    surf_usm_v(l)%tt_surface_window_m(m) = stend_window
    79307981                    surf_usm_v(l)%tt_surface_green_m(m) = stend_green
    7931                  ELSEIF ( intermediate_timestep_count <                        &
     7982                 ELSEIF ( intermediate_timestep_count <                                 &
    79327983                          intermediate_timestep_count_max )  THEN
    7933                     surf_usm_v(l)%tt_surface_m(m) = -9.5625_wp * stend +       &
     7984                    surf_usm_v(l)%tt_surface_m(m) = -9.5625_wp * stend +                &
    79347985                                     5.3125_wp * surf_usm_v(l)%tt_surface_m(m)
    7935                     surf_usm_v(l)%tt_surface_green_m(m) = -9.5625_wp * stend_green +       &
     7986                    surf_usm_v(l)%tt_surface_green_m(m) = -9.5625_wp * stend_green +    &
    79367987                                     5.3125_wp * surf_usm_v(l)%tt_surface_green_m(m)
    7937                     surf_usm_v(l)%tt_surface_window_m(m) = -9.5625_wp * stend_window +       &
     7988                    surf_usm_v(l)%tt_surface_window_m(m) = -9.5625_wp * stend_window +  &
    79387989                                     5.3125_wp * surf_usm_v(l)%tt_surface_window_m(m)
    79397990                 ENDIF
     
    79437994!--           update the radiative fluxes in order to keep the solution stable
    79447995
    7945               IF ( ( ABS( t_surf_v_p(l)%t(m) - t_surf_v(l)%t(m) ) > 1.0_wp ) .OR. &
     7996              IF ( ( ( ABS( t_surf_v_p(l)%t(m) - t_surf_v(l)%t(m) ) > 1.0_wp ) .OR.            &
    79467997                   ( ABS( t_surf_green_v_p(l)%t(m) - t_surf_green_v(l)%t(m) ) > 1.0_wp ) .OR.  &
    7947                    ( ABS( t_surf_window_v_p(l)%t(m) - t_surf_window_v(l)%t(m) ) > 1.0_wp ) ) THEN
     7998                   ( ABS( t_surf_window_v_p(l)%t(m) - t_surf_window_v(l)%t(m) ) > 1.0_wp ) )   &
     7999                     .AND.  unscheduled_radiation_calls ) THEN
    79488000                 force_radiation_call_l = .TRUE.
    79498001              ENDIF
Note: See TracChangeset for help on using the changeset viewer.