Ignore:
Timestamp:
Jan 11, 2018 2:58:11 PM (6 years ago)
Author:
kanani
Message:

Removed unused variables t_surf_whole...

File:
1 edited

Legend:

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

    r2735 r2737  
    1717! Copyright 2015-2018 Czech Technical University in Prague
    1818! Copyright 1997-2018 Leibniz Universitaet Hannover
    19 !--------------------------------------------------------------------------------!
     19!------------------------------------------------------------------------------!
    2020!
    2121! Current revisions:
     
    2626! -----------------
    2727! $Id$
     28! Removed unused variables t_surf_whole...
     29!
     30! 2735 2018-01-11 12:01:27Z suehring
    2831! resistances are saved in surface attributes
    2932!
     
    529532    REAL(wp), DIMENSION(:), ALLOCATABLE, TARGET    :: t_surf_green_h     !< green surface temperature (K) at horizontal walls
    530533    REAL(wp), DIMENSION(:), ALLOCATABLE, TARGET    :: t_surf_green_h_p   !< progn. green surface temperature (K) at horizontal walls
    531     REAL(wp), DIMENSION(:), ALLOCATABLE, TARGET    :: t_surf_whole_h     !< whole surface temperature (K) at horizontal walls
    532     REAL(wp), DIMENSION(:), ALLOCATABLE, TARGET    :: t_surf_whole_h_p   !< progn. whole surface temperature (K) at horizontal walls
    533534    REAL(wp), DIMENSION(:), ALLOCATABLE, TARGET    :: t_surf_10cm_h      !< near surface temperature (10cm) (K) at horizontal walls
    534535    REAL(wp), DIMENSION(:), ALLOCATABLE, TARGET    :: t_surf_10cm_h_p    !< progn. near surface temperature (10cm) (K) at horizontal walls
     
    539540    TYPE(t_surf_vertical), DIMENSION(0:3), TARGET  ::  t_surf_green_v
    540541    TYPE(t_surf_vertical), DIMENSION(0:3), TARGET  ::  t_surf_green_v_p
    541     TYPE(t_surf_vertical), DIMENSION(0:3), TARGET  ::  t_surf_whole_v
    542     TYPE(t_surf_vertical), DIMENSION(0:3), TARGET  ::  t_surf_whole_v_p
    543542    TYPE(t_surf_vertical), DIMENSION(0:3), TARGET  ::  t_surf_10cm_v
    544543    TYPE(t_surf_vertical), DIMENSION(0:3), TARGET  ::  t_surf_10cm_v_p
     
    550549    REAL(wp), DIMENSION(:), POINTER                :: t_surf_green_h
    551550    REAL(wp), DIMENSION(:), POINTER                :: t_surf_green_h_p
    552     REAL(wp), DIMENSION(:), POINTER                :: t_surf_whole_h
    553     REAL(wp), DIMENSION(:), POINTER                :: t_surf_whole_h_p
    554551    REAL(wp), DIMENSION(:), POINTER                :: t_surf_10cm_h
    555552    REAL(wp), DIMENSION(:), POINTER                :: t_surf_10cm_h_p
     
    561558    REAL(wp), DIMENSION(:), ALLOCATABLE, TARGET    :: t_surf_green_h_1
    562559    REAL(wp), DIMENSION(:), ALLOCATABLE, TARGET    :: t_surf_green_h_2
    563     REAL(wp), DIMENSION(:), ALLOCATABLE, TARGET    :: t_surf_whole_h_1
    564     REAL(wp), DIMENSION(:), ALLOCATABLE, TARGET    :: t_surf_whole_h_2
    565560    REAL(wp), DIMENSION(:), ALLOCATABLE, TARGET    :: t_surf_10cm_h_1
    566561    REAL(wp), DIMENSION(:), ALLOCATABLE, TARGET    :: t_surf_10cm_h_2
     
    572567    TYPE(t_surf_vertical), DIMENSION(:), POINTER ::  t_surf_green_v
    573568    TYPE(t_surf_vertical), DIMENSION(:), POINTER ::  t_surf_green_v_p
    574     TYPE(t_surf_vertical), DIMENSION(:), POINTER ::  t_surf_whole_v
    575     TYPE(t_surf_vertical), DIMENSION(:), POINTER ::  t_surf_whole_v_p
    576569    TYPE(t_surf_vertical), DIMENSION(:), POINTER ::  t_surf_10cm_v
    577570    TYPE(t_surf_vertical), DIMENSION(:), POINTER ::  t_surf_10cm_v_p
     
    583576    TYPE(t_surf_vertical), DIMENSION(0:3), TARGET  :: t_surf_green_v_1
    584577    TYPE(t_surf_vertical), DIMENSION(0:3), TARGET  :: t_surf_green_v_2
    585     TYPE(t_surf_vertical), DIMENSION(0:3), TARGET  :: t_surf_whole_v_1
    586     TYPE(t_surf_vertical), DIMENSION(0:3), TARGET  :: t_surf_whole_v_2
    587578    TYPE(t_surf_vertical), DIMENSION(0:3), TARGET  :: t_surf_10cm_v_1
    588579    TYPE(t_surf_vertical), DIMENSION(0:3), TARGET  :: t_surf_10cm_v_2
     
    592583    REAL(wp), DIMENSION(:), ALLOCATABLE, TARGET    :: t_surf_window_av   !< average of window surface temperature (K)
    593584    REAL(wp), DIMENSION(:), ALLOCATABLE, TARGET    :: t_surf_green_av    !< average of green wall surface temperature (K)
    594     REAL(wp), DIMENSION(:), ALLOCATABLE, TARGET    :: t_surf_whole_av    !< average of whole wall surface temperature (K)
    595585    REAL(wp), DIMENSION(:), ALLOCATABLE, TARGET    :: t_surf_10cm_av    !< average of whole wall surface temperature (K)
    596586
     
    941931        IF ( .NOT. ALLOCATED( t_green_h_p ) )                                  &           
    942932           ALLOCATE ( t_green_h_p(nzb_wall:nzt_wall+1,1:surf_usm_h%ns) ) 
    943         IF ( .NOT. ALLOCATED( t_surf_whole_h ) )                               &
    944            ALLOCATE ( t_surf_whole_h(1:surf_usm_h%ns) )
    945         IF ( .NOT. ALLOCATED( t_surf_whole_h_p ) )                             &
    946            ALLOCATE ( t_surf_whole_h_p(1:surf_usm_h%ns) )           
    947933        IF ( .NOT. ALLOCATED( t_surf_10cm_h ) )                                &
    948934           ALLOCATE ( t_surf_10cm_h(1:surf_usm_h%ns) )
     
    977963        IF ( .NOT. ALLOCATED( t_green_h_2 ) )                                  &           
    978964           ALLOCATE ( t_green_h_2(nzb_wall:nzt_wall+1,1:surf_usm_h%ns) )         
    979         IF ( .NOT. ALLOCATED( t_surf_whole_h_1 ) )                             &
    980            ALLOCATE ( t_surf_whole_h_1(1:surf_usm_h%ns) )
    981         IF ( .NOT. ALLOCATED( t_surf_whole_h_2 ) )                             &
    982            ALLOCATE ( t_surf_whole_h_2(1:surf_usm_h%ns) )
    983965        IF ( .NOT. ALLOCATED( t_surf_10cm_h_1 ) )                              &
    984966           ALLOCATE ( t_surf_10cm_h_1(1:surf_usm_h%ns) )
     
    993975        t_surf_window_h => t_surf_window_h_1; t_surf_window_h_p => t_surf_window_h_2 
    994976        t_surf_green_h => t_surf_green_h_1; t_surf_green_h_p => t_surf_green_h_2           
    995         t_surf_whole_h => t_surf_whole_h_1; t_surf_whole_h_p => t_surf_whole_h_2
    996977        t_surf_10cm_h => t_surf_10cm_h_1; t_surf_10cm_h_p => t_surf_10cm_h_2 
    997978 
     
    10251006           IF ( .NOT. ALLOCATED( t_surf_green_v_p(l)%t ) )                     &
    10261007              ALLOCATE ( t_surf_green_v_p(l)%t(1:surf_usm_v(l)%ns) )
    1027            IF ( .NOT. ALLOCATED( t_surf_whole_v(l)%t ) )                       &
    1028               ALLOCATE ( t_surf_whole_v(l)%t(1:surf_usm_v(l)%ns) )
    1029            IF ( .NOT. ALLOCATED( t_surf_whole_v_p(l)%t ) )                     &
    1030               ALLOCATE ( t_surf_whole_v_p(l)%t(1:surf_usm_v(l)%ns) )
    10311008           IF ( .NOT. ALLOCATED( t_surf_10cm_v(l)%t ) )                        &
    10321009              ALLOCATE ( t_surf_10cm_v(l)%t(1:surf_usm_v(l)%ns) )
     
    10631040           IF ( .NOT. ALLOCATED( t_green_v_2(l)%t ) )                          &           
    10641041              ALLOCATE ( t_green_v_2(l)%t(nzb_wall:nzt_wall+1,1:surf_usm_v(l)%ns) ) 
    1065            IF ( .NOT. ALLOCATED( t_surf_whole_v_1(l)%t ) )                     &
    1066               ALLOCATE ( t_surf_whole_v_1(l)%t(1:surf_usm_v(l)%ns) )
    1067            IF ( .NOT. ALLOCATED( t_surf_whole_v_2(l)%t ) )                     &
    1068               ALLOCATE ( t_surf_whole_v_2(l)%t(1:surf_usm_v(l)%ns) )
    10691042           IF ( .NOT. ALLOCATED( t_surf_10cm_v_1(l)%t ) )                     &
    10701043              ALLOCATE ( t_surf_10cm_v_1(l)%t(1:surf_usm_v(l)%ns) )
     
    10801053        t_surf_window_v => t_surf_window_v_1; t_surf_window_v_p => t_surf_window_v_2
    10811054        t_surf_green_v => t_surf_green_v_1; t_surf_green_v_p => t_surf_green_v_2
    1082         t_surf_whole_v => t_surf_whole_v_1; t_surf_whole_v_p => t_surf_whole_v_2
    10831055        t_surf_10cm_v => t_surf_10cm_v_1; t_surf_10cm_v_p => t_surf_10cm_v_2
    10841056
     
    14541426                    ENDDO
    14551427               
    1456                 CASE ( 'usm_t_surf_whole' )
    1457 !--                 surface temperature for whole surfaces
    1458                     IF ( .NOT.  ALLOCATED(surf_usm_h%t_surf_whole_av) )  THEN
    1459                         ALLOCATE( surf_usm_h%t_surf_whole_av(1:surf_usm_h%ns) )
    1460                         surf_usm_h%t_surf_whole_av = 0.0_wp
    1461                     ENDIF
    1462                     DO  l = 0, 3
    1463                        IF ( .NOT.  ALLOCATED(surf_usm_v(l)%t_surf_whole_av) )  THEN
    1464                            ALLOCATE( surf_usm_v(l)%t_surf_whole_av(1:surf_usm_v(l)%ns) )
    1465                            surf_usm_v(l)%t_surf_whole_av = 0.0_wp
    1466                        ENDIF
    1467                     ENDDO
    1468                    
    14691428                CASE ( 'usm_t_surf_10cm' )
    14701429!--                 near surface temperature for whole surfaces
     
    17851744                    ENDDO
    17861745               
    1787                 CASE ( 'usm_t_surf_whole' )
    1788 !--                 surface temperature for whole surfaces
    1789                     DO  m = 1, surf_usm_h%ns
    1790                        surf_usm_h%t_surf_whole_av(m) =                               &
    1791                                           surf_usm_h%t_surf_whole_av(m) +            &
    1792                                           t_surf_whole_h(m)
    1793                     ENDDO
    1794                     DO  l = 0, 3
    1795                        DO  m = 1, surf_usm_v(l)%ns
    1796                           surf_usm_v(l)%t_surf_whole_av(m) =                         &
    1797                                           surf_usm_v(l)%t_surf_whole_av(m) +         &
    1798                                           t_surf_whole_v(l)%t(m)
    1799                        ENDDO
    1800                     ENDDO
    1801                    
    18021746                CASE ( 'usm_t_surf_10cm' )
    18031747!--                 near surface temperature for whole surfaces
     
    21192063                          surf_usm_v(l)%t_surf_green_av(m) =                         &
    21202064                                          surf_usm_v(l)%t_surf_green_av(m) /         &
    2121                                           REAL( average_count_3d, kind=wp )
    2122                        ENDDO
    2123                     ENDDO
    2124                    
    2125                 CASE ( 'usm_t_surf_whole' )
    2126 !--                 surface temperature for whole surfaces
    2127                     DO  m = 1, surf_usm_h%ns
    2128                        surf_usm_h%t_surf_whole_av(m) =                               &
    2129                                           surf_usm_h%t_surf_whole_av(m) /            &
    2130                                           REAL( average_count_3d, kind=wp )
    2131                     ENDDO
    2132                     DO  l = 0, 3
    2133                        DO  m = 1, surf_usm_v(l)%ns
    2134                           surf_usm_v(l)%t_surf_whole_av(m) =                         &
    2135                                           surf_usm_v(l)%t_surf_whole_av(m) /         &
    21362065                                          REAL( average_count_3d, kind=wp )
    21372066                       ENDDO
     
    22792208                  var(1:12) == 'usm_t_window' .OR. var(1:17) == 'usm_t_surf_window' .OR.  &
    22802209                  var(1:16) == 'usm_t_surf_green'  .OR.                                   &
    2281                   var(1:16) == 'usm_t_surf_whole' .OR. var(1:11) == 'usm_t_green' .OR.    &
     2210                  var(1:11) == 'usm_t_green' .OR.                                         &
    22822211                  var(1:15) == 'usm_t_surf_10cm')  THEN
    22832212            unit = 'K'
     
    30622991              ENDIF
    30632992
    3064           CASE ( 'usm_t_surf_whole' )
    3065 !--           surface temperature for whole surfaces
    3066 
    3067               IF ( av == 0 )  THEN
    3068                  DO  m = 1, surf_usm_h%ns
    3069                     i = surf_usm_h%i(m)
    3070                     j = surf_usm_h%j(m)
    3071                     k = surf_usm_h%k(m)
    3072                     temp_pf(k,j,i) = t_surf_whole_h(m)
    3073                  ENDDO
    3074                  DO  l = 0, 3
    3075                     DO  m = 1, surf_usm_v(l)%ns
    3076                        i = surf_usm_v(l)%i(m)
    3077                        j = surf_usm_v(l)%j(m)
    3078                        k = surf_usm_v(l)%k(m)
    3079                        temp_pf(k,j,i) = t_surf_whole_v(l)%t(m)
    3080                     ENDDO
    3081                  ENDDO
    3082 
    3083               ELSE
    3084                  DO  m = 1, surf_usm_h%ns
    3085                     i = surf_usm_h%i(m)
    3086                     j = surf_usm_h%j(m)
    3087                     k = surf_usm_h%k(m)
    3088                     temp_pf(k,j,i) = surf_usm_h%t_surf_whole_av(m)
    3089                  ENDDO
    3090                  DO  l = 0, 3
    3091                     DO  m = 1, surf_usm_v(l)%ns
    3092                        i = surf_usm_v(l)%i(m)
    3093                        j = surf_usm_v(l)%j(m)
    3094                        k = surf_usm_v(l)%k(m)
    3095                        temp_pf(k,j,i) = surf_usm_v(l)%t_surf_whole_av(m)
    3096                     ENDDO
    3097 
    3098                  ENDDO
    3099 
    3100               ENDIF
    3101              
    31022993          CASE ( 'usm_t_surf_10cm' )
    31032994!--           near surface temperature for whole surfaces
     
    32923183             var(1:10) == 'usm_t_surf'  .OR.  var(1:10) == 'usm_t_wall'  .OR.               &
    32933184             var(1:17) == 'usm_t_surf_window'  .OR.  var(1:12) == 'usm_t_window'  .OR.      &
    3294              var(1:16) == 'usm_t_surf_green'  .OR.  var(1:16) == 'usm_t_surf_whole' .OR.    &
     3185             var(1:16) == 'usm_t_surf_green'  .OR.                                          &
    32953186             var(1:15) == 'usm_t_surf_10cm' .OR.                                            &
    32963187             var(1:9) == 'usm_surfz'  .OR.  var(1:7) == 'usm_svf'  .OR.                     &
     
    44884379               t_surf_window_h(m) = pt(k,j,i) * exn
    44894380               t_surf_green_h(m) = pt(k,j,i) * exn
    4490                t_surf_whole_h(m) = pt(k,j,i) * exn
     4381               surf_usm_h%pt_surface(m) = pt(k,j,i) * exn
    44914382            ENDDO
    44924383!
     
    45014392                  t_surf_window_v(l)%t(m) = pt(k,j,i) * exn
    45024393                  t_surf_green_v(l)%t(m) = pt(k,j,i) * exn
    4503                   t_surf_whole_v(l)%t(m) = pt(k,j,i) * exn
     4394                  surf_usm_v(l)%pt_surface(m) = pt(k,j,i) * exn
    45044395               ENDDO
    45054396            ENDDO
     
    45634454        t_surf_window_h_p = t_surf_window_h
    45644455        t_surf_window_v_p = t_surf_window_v
    4565         t_surf_whole_h_p = t_surf_whole_h
    4566         t_surf_whole_v_p = t_surf_whole_v
    45674456        t_surf_green_h_p = t_surf_green_h
    45684457        t_surf_green_v_p = t_surf_green_v
     
    51515040          k = surf_usm_h%k(m)
    51525041
    5153           t_surf_10cm_h(m) = t_surf_whole_h(m) + surf_usm_h%ts(m) / kappa        &
     5042          t_surf_10cm_h(m) = surf_usm_h%pt_surface(m) + surf_usm_h%ts(m) / kappa        &
    51545043                             * ( log( 0.1_wp /  surf_usm_h%z0h(m) )              &
    51555044                               - psi_h( 0.1_wp / surf_usm_h%ol(m) )              &
     
    51675056             k = surf_usm_v(l)%k(m)
    51685057
    5169              t_surf_10cm_v(l)%t(m) = t_surf_whole_v(l)%t(m) + surf_usm_v(l)%ts(m) / kappa &
     5058             t_surf_10cm_v(l)%t(m) =surf_usm_v(l)%pt_surface(m) + surf_usm_v(l)%ts(m) / kappa &
    51705059                                     * ( log( 0.1_wp / surf_usm_v(l)%z0h(m) )             &
    51715060                                       - psi_h( 0.1_wp / surf_usm_v(l)%ol(m) )            &
     
    73857274       t_green_h    = t_green_h_p
    73867275       t_green_v    = t_green_v_p
    7387        t_surf_whole_h    = t_surf_whole_h_p
    7388        t_surf_whole_v    = t_surf_whole_v_p
    73897276#else
    73907277       SELECT CASE ( mod_count )
     
    73987285             t_surf_green_h  => t_surf_green_h_1; t_surf_green_h_p  => t_surf_green_h_2
    73997286             t_green_h     => t_green_h_1;    t_green_h_p     => t_green_h_2
    7400              t_surf_whole_h  => t_surf_whole_h_1; t_surf_whole_h_p  => t_surf_whole_h_2
    74017287!
    74027288!--          Vertical surfaces
     
    74077293             t_surf_green_v  => t_surf_green_v_1; t_surf_green_v_p  => t_surf_green_v_2
    74087294             t_green_v     => t_green_v_1;    t_green_v_p     => t_green_v_2
    7409              t_surf_whole_v  => t_surf_whole_v_1; t_surf_whole_v_p  => t_surf_whole_v_2
    74107295          CASE ( 1 )
    74117296!
     
    74177302             t_surf_green_h  => t_surf_green_h_2; t_surf_green_h_p  => t_surf_green_h_1
    74187303             t_green_h     => t_green_h_2;    t_green_h_p     => t_green_h_1
    7419              t_surf_whole_h  => t_surf_whole_h_2; t_surf_whole_h_p  => t_surf_whole_h_1
    74207304!
    74217305!--          Vertical surfaces
     
    74267310             t_surf_green_v  => t_surf_green_v_2; t_surf_green_v_p  => t_surf_green_v_1
    74277311             t_green_v     => t_green_v_2;    t_green_v_p     => t_green_v_1
    7428              t_surf_whole_v  => t_surf_whole_v_2; t_surf_whole_v_p  => t_surf_whole_v_1
    74297312       END SELECT
    74307313#endif
Note: See TracChangeset for help on using the changeset viewer.