Ignore:
Timestamp:
Dec 19, 2018 1:48:34 PM (5 years ago)
Author:
raasch
Message:

nopointer option removed

File:
1 edited

Legend:

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

    r3614 r3636  
    2828! -----------------
    2929! $Id$
     30! nopointer option removed
     31!
     32! 3614 2018-12-10 07:05:46Z raasch
    3033! unused variables removed
    3134!
     
    393396
    394397    USE arrays_3d,                                                             &
    395 #if ! defined( __nopointer )
    396398        ONLY:  hyp, zu, pt, p, u, v, w, tend, exner, hyrho, prr, q, ql, vpt
    397 #else
    398         ONLY:  hyp,     pt,    u, v, w, tend, exner, hyrho, prr, q, ql, vpt
    399 #endif
     399
    400400    USE calc_mean_profile_mod,                                                 &
    401401        ONLY:  calc_mean_profile
     
    936936    END TYPE surf_type_usm
    937937   
    938 #if defined( __nopointer )
    939     TYPE(surf_type_usm), TARGET   ::  m_liq_usm_h,        & !< liquid water reservoir (m), horizontal surface elements
    940                                       m_liq_usm_h_p         !< progn. liquid water reservoir (m), horizontal surface elements
    941 
    942     TYPE(surf_type_usm), DIMENSION(0:3), TARGET   ::  &
    943                                       m_liq_usm_v,        & !< liquid water reservoir (m), vertical surface elements
    944                                       m_liq_usm_v_p         !< progn. liquid water reservoir (m), vertical surface elements
    945 #else
    946938    TYPE(surf_type_usm), POINTER  ::  m_liq_usm_h,        & !< liquid water reservoir (m), horizontal surface elements
    947939                                      m_liq_usm_h_p         !< progn. liquid water reservoir (m), horizontal surface elements
     
    957949                                      m_liq_usm_v_1,      & !<
    958950                                      m_liq_usm_v_2         !<
    959 #endif
    960951
    961952    TYPE(surf_type_usm), TARGET ::  tm_liq_usm_h_m      !< liquid water reservoir tendency (m), horizontal surface elements
     
    1006997    REAL(wp), DIMENSION(:), ALLOCATABLE            :: zwn_green          !< normalized green layer depths (m)
    1007998
    1008 #if defined( __nopointer )
    1009     REAL(wp), DIMENSION(:), ALLOCATABLE, TARGET    :: t_surf_wall_h           !< wall surface temperature (K) at horizontal walls
    1010     REAL(wp), DIMENSION(:), ALLOCATABLE, TARGET    :: t_surf_wall_h_p         !< progn. wall surface temperature (K) at horizontal walls
    1011     REAL(wp), DIMENSION(:), ALLOCATABLE, TARGET    :: t_surf_window_h    !< window surface temperature (K) at horizontal walls
    1012     REAL(wp), DIMENSION(:), ALLOCATABLE, TARGET    :: t_surf_window_h_p  !< progn. window surface temperature (K) at horizontal walls
    1013     REAL(wp), DIMENSION(:), ALLOCATABLE, TARGET    :: t_surf_green_h     !< green surface temperature (K) at horizontal walls
    1014     REAL(wp), DIMENSION(:), ALLOCATABLE, TARGET    :: t_surf_green_h_p   !< progn. green surface temperature (K) at horizontal walls
    1015     TYPE(t_surf_vertical), DIMENSION(0:3), TARGET  ::  t_surf_wall_v
    1016     TYPE(t_surf_vertical), DIMENSION(0:3), TARGET  ::  t_surf_wall_v_p
    1017     TYPE(t_surf_vertical), DIMENSION(0:3), TARGET  ::  t_surf_window_v
    1018     TYPE(t_surf_vertical), DIMENSION(0:3), TARGET  ::  t_surf_window_v_p
    1019     TYPE(t_surf_vertical), DIMENSION(0:3), TARGET  ::  t_surf_green_v
    1020     TYPE(t_surf_vertical), DIMENSION(0:3), TARGET  ::  t_surf_green_v_p
    1021 #else
    1022999    REAL(wp), DIMENSION(:), POINTER                :: t_surf_wall_h
    10231000    REAL(wp), DIMENSION(:), POINTER                :: t_surf_wall_h_p
     
    10471024    TYPE(t_surf_vertical), DIMENSION(0:3), TARGET  :: t_surf_green_v_1
    10481025    TYPE(t_surf_vertical), DIMENSION(0:3), TARGET  :: t_surf_green_v_2
    1049    
    1050 #endif
    10511026
    10521027!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     
    10551030!-- parameters of the land, roof and wall surfaces
    10561031
    1057 #if defined( __nopointer )
    1058     REAL(wp), DIMENSION(:,:), ALLOCATABLE, TARGET    :: t_wall_h             !< Wall temperature (K)
    1059     REAL(wp), DIMENSION(:,:), ALLOCATABLE, TARGET    :: t_wall_h_p           !< Prog. wall temperature (K)
    1060     REAL(wp), DIMENSION(:,:), ALLOCATABLE, TARGET    :: t_window_h           !< Window temperature (K)
    1061     REAL(wp), DIMENSION(:,:), ALLOCATABLE, TARGET    :: t_window_h_p         !< Prog. window temperature (K)
    1062     REAL(wp), DIMENSION(:,:), ALLOCATABLE, TARGET    :: t_green_h            !< Green temperature (K)
    1063     REAL(wp), DIMENSION(:,:), ALLOCATABLE, TARGET    :: t_green_h_p          !< Prog. green temperature (K)
    1064     REAL(wp), DIMENSION(:,:), ALLOCATABLE, TARGET    :: swc_h              !< soil water content green building layer
    1065     REAL(wp), DIMENSION(:,:), ALLOCATABLE, TARGET    :: swc_h_av              !< avg of soil water content green building layer
    1066     REAL(wp), DIMENSION(:,:), ALLOCATABLE, TARGET    :: swc_h_p              !< Prog. soil water content green building layer
    1067     REAL(wp), DIMENSION(:,:), ALLOCATABLE, TARGET    :: swc_sat_h          !< soil water content green building layer at saturation
    1068     REAL(wp), DIMENSION(:,:), ALLOCATABLE, TARGET    :: swc_res_h          !< soil water content green building layer residual
    1069     REAL(wp), DIMENSION(:,:), ALLOCATABLE, TARGET    :: rootfr_h           !< root fraction green green building layer
    1070     REAL(wp), DIMENSION(:,:), ALLOCATABLE, TARGET    :: wilt_h             !< wilting point green building layer
    1071     REAL(wp), DIMENSION(:,:), ALLOCATABLE, TARGET    :: fc_h               !< field capacity green building layer
    1072 
    1073 
    1074     TYPE(t_wall_vertical), DIMENSION(0:3), TARGET  :: t_wall_v             !< Wall temperature (K)
    1075     TYPE(t_wall_vertical), DIMENSION(0:3), TARGET  :: t_wall_v_p           !< Prog. wall temperature (K)
    1076     TYPE(t_wall_vertical), DIMENSION(0:3), TARGET  :: t_window_v           !< Window temperature (K)
    1077     TYPE(t_wall_vertical), DIMENSION(0:3), TARGET  :: t_window_v_p         !< Prog. window temperature (K)
    1078     TYPE(t_wall_vertical), DIMENSION(0:3), TARGET  :: t_green_v            !< Green temperature (K)
    1079     TYPE(t_wall_vertical), DIMENSION(0:3), TARGET  :: t_green_v_p          !< Prog. green temperature (K)
    1080     TYPE(t_wall_vertical), DIMENSION(0:3), TARGET  :: swc_v             !< Wall swc
    1081     TYPE(t_wall_vertical), DIMENSION(0:3), TARGET  :: swc_v_p           !< Prog. swc
    1082    
    1083 #else
    10841032    REAL(wp), DIMENSION(:,:), POINTER                :: t_wall_h, t_wall_h_p
    10851033    REAL(wp), DIMENSION(:,:), ALLOCATABLE, TARGET    :: t_wall_h_1, t_wall_h_2
     
    11011049    TYPE(t_wall_vertical), DIMENSION(:), POINTER   :: swc_v, swc_v_p
    11021050    TYPE(t_wall_vertical), DIMENSION(0:3), TARGET  :: swc_v_1, swc_v_2
    1103 #endif
    11041051
    11051052!-- Surface and material parameters classes (surface_type)
     
    14171364
    14181365!--     allocate wall and roof temperature arrays, for horizontal walls
    1419 #if defined( __nopointer )
    1420         IF ( .NOT. ALLOCATED( t_surf_wall_h ) )                                     &
    1421            ALLOCATE ( t_surf_wall_h(1:surf_usm_h%ns) )
    1422         IF ( .NOT. ALLOCATED( t_surf_wall_h_p ) )                                   &
    1423            ALLOCATE ( t_surf_wall_h_p(1:surf_usm_h%ns) )
    1424         IF ( .NOT. ALLOCATED( t_wall_h ) )                                     &           
    1425            ALLOCATE ( t_wall_h(nzb_wall:nzt_wall+1,1:surf_usm_h%ns) )
    1426         IF ( .NOT. ALLOCATED( t_wall_h_p ) )                                   &           
    1427            ALLOCATE ( t_wall_h_p(nzb_wall:nzt_wall+1,1:surf_usm_h%ns) ) 
    1428         IF ( .NOT. ALLOCATED( t_surf_window_h ) )                              &
    1429            ALLOCATE ( t_surf_window_h(1:surf_usm_h%ns) )
    1430         IF ( .NOT. ALLOCATED( t_surf_window_h_p ) )                            &
    1431            ALLOCATE ( t_surf_window_h_p(1:surf_usm_h%ns) )
    1432         IF ( .NOT. ALLOCATED( t_window_h ) )                                   &           
    1433            ALLOCATE ( t_window_h(nzb_wall:nzt_wall+1,1:surf_usm_h%ns) )
    1434         IF ( .NOT. ALLOCATED( t_window_h_p ) )                                 &           
    1435            ALLOCATE ( t_window_h_p(nzb_wall:nzt_wall+1,1:surf_usm_h%ns) ) 
    1436         IF ( .NOT. ALLOCATED( t_surf_green_h ) )                               &
    1437            ALLOCATE ( t_surf_green_h(1:surf_usm_h%ns) )
    1438         IF ( .NOT. ALLOCATED( t_surf_green_h_p ) )                             &
    1439            ALLOCATE ( t_surf_green_h_p(1:surf_usm_h%ns) )           
    1440         IF ( .NOT. ALLOCATED( t_green_h ) )                                    &           
    1441            ALLOCATE ( t_green_h(nzb_wall:nzt_wall+1,1:surf_usm_h%ns) )
    1442         IF ( .NOT. ALLOCATED( t_green_h_p ) )                                  &           
    1443            ALLOCATE ( t_green_h_p(nzb_wall:nzt_wall+1,1:surf_usm_h%ns) ) 
    1444         IF ( .NOT. ALLOCATED( swc_h ) )                                    &           
    1445            ALLOCATE ( swc_h(nzb_wall:nzt_wall+1,1:surf_usm_h%ns) )
    1446         IF ( .NOT. ALLOCATED( swc_sat_h ) )                                    &           
    1447            ALLOCATE ( swc_sat_h(nzb_wall:nzt_wall+1,1:surf_usm_h%ns) )
    1448         IF ( .NOT. ALLOCATED( swc_res_h ) )                                    &           
    1449            ALLOCATE ( swc_res_h(nzb_wall:nzt_wall+1,1:surf_usm_h%ns) )
    1450         IF ( .NOT. ALLOCATED( rootfr_h ) )                                    &           
    1451            ALLOCATE ( rootfr_h(nzb_wall:nzt_wall+1,1:surf_usm_h%ns) )
    1452         IF ( .NOT. ALLOCATED( wilt_h ) )                                    &           
    1453            ALLOCATE ( wilt_h(nzb_wall:nzt_wall+1,1:surf_usm_h%ns) )
    1454         IF ( .NOT. ALLOCATED( fc_h ) )                                    &           
    1455            ALLOCATE ( fc_h(nzb_wall:nzt_wall+1,1:surf_usm_h%ns) )
    1456 
    1457        IF ( .NOT. ALLOCATED( m_liq_usm_h%var_usm_1d ) )                            &
    1458           ALLOCATE ( m_liq_usm_h%var_usm_1d(1:surf_usm_h%ns) )
    1459 
    1460 !--    Horizontal surfaces
    1461        ALLOCATE ( m_liq_usm_h_p%var_usm_1d(1:surf_usm_h%ns)                      )
    1462 !
    1463 !--    Vertical surfaces
    1464        DO  l = 0, 3
    1465           ALLOCATE ( m_liq_usm_v_p(l)%var_usm_1d(1:surf_usm_v(l)%ns)                      )
    1466        ENDDO
    1467          
    1468 #else
    14691366!
    14701367!--     Allocate if required. Note, in case of restarts, some of these arrays
     
    15291426        wilt_h       => wilt_h_1
    15301427        fc_h       => fc_h_1
    1531  
    1532 #endif
    15331428
    15341429!--     allocate wall and roof temperature arrays, for vertical walls if required
    1535 #if defined( __nopointer )
    1536         DO  l = 0, 3
    1537            IF ( .NOT. ALLOCATED( t_surf_wall_v(l)%t ) )                             &
    1538               ALLOCATE ( t_surf_wall_v(l)%t(1:surf_usm_v(l)%ns) )
    1539            IF ( .NOT. ALLOCATED( t_surf_wall_v_p(l)%t ) )                           &
    1540               ALLOCATE ( t_surf_wall_v_p(l)%t(1:surf_usm_v(l)%ns) )
    1541            IF ( .NOT. ALLOCATED( t_wall_v(l)%t ) )                             &
    1542               ALLOCATE ( t_wall_v(l)%t(nzb_wall:nzt_wall+1,1:surf_usm_v(l)%ns) )
    1543            IF ( .NOT. ALLOCATED( t_wall_v_p(l)%t ) )                           &                 
    1544               ALLOCATE ( t_wall_v_p(l)%t(nzb_wall:nzt_wall+1,1:surf_usm_v(l)%ns) )
    1545            IF ( .NOT. ALLOCATED( t_surf_window_v(l)%t ) )                      &
    1546               ALLOCATE ( t_surf_window_v(l)%t(1:surf_usm_v(l)%ns) )
    1547            IF ( .NOT. ALLOCATED( t_surf_window_v_p(l)%t ) )                    &
    1548               ALLOCATE ( t_surf_window_v_p(l)%t(1:surf_usm_v(l)%ns) )
    1549            IF ( .NOT. ALLOCATED( t_window_v(l)%t ) )                           &
    1550               ALLOCATE ( t_window_v(l)%t(nzb_wall:nzt_wall+1,1:surf_usm_v(l)%ns) )
    1551            IF ( .NOT. ALLOCATED( t_window_v_p(l)%t ) )                         &                 
    1552               ALLOCATE ( t_window_v_p(l)%t(nzb_wall:nzt_wall+1,1:surf_usm_v(l)%ns) )
    1553            IF ( .NOT. ALLOCATED( t_green_v(l)%t ) )                            &
    1554               ALLOCATE ( t_green_v(l)%t(nzb_wall:nzt_wall+1,1:surf_usm_v(l)%ns) )
    1555            IF ( .NOT. ALLOCATED( t_green_v_p(l)%t ) )                          &                 
    1556               ALLOCATE ( t_green_v_p(l)%t(nzb_wall:nzt_wall+1,1:surf_usm_v(l)%ns) )
    1557            IF ( .NOT. ALLOCATED( t_surf_green_v(l)%t ) )                       &
    1558               ALLOCATE ( t_surf_green_v(l)%t(1:surf_usm_v(l)%ns) )
    1559            IF ( .NOT. ALLOCATED( t_surf_green_v_p(l)%t ) )                     &
    1560               ALLOCATE ( t_surf_green_v_p(l)%t(1:surf_usm_v(l)%ns) )
    1561            IF ( .NOT. ALLOCATED( m_liq_usm_v(l)%var_usm_1d ) )                 &
    1562              ALLOCATE ( m_liq_usm_v(l)%var_usm_1d(1:surf_usm_v(l)%ns) )
    1563            IF ( .NOT. ALLOCATED( swc_v(l)%t ) )                             &
    1564               ALLOCATE ( swc_v(l)%t(nzb_wall:nzt_wall+1,1:surf_usm_v(l)%ns) )
    1565            IF ( .NOT. ALLOCATED( swc_v_p(l)%t ) )                           &                 
    1566               ALLOCATE ( swc_v_p(l)%t(nzb_wall:nzt_wall+1,1:surf_usm_v(l)%ns) )
    1567         ENDDO
    1568 #else
    15691430!
    15701431!--     Allocate if required. Note, in case of restarts, some of these arrays
     
    16151476        swc_v    => swc_v_1;    swc_v_p    => swc_v_2
    16161477
    1617 #endif
    16181478!
    16191479!--     Allocate intermediate timestep arrays. For horizontal surfaces.
     
    40593919        REAL(wp)     ::  z_agl                        !< height above ground
    40603920
    4061 !
    4062 !-- NOPOINTER version not implemented yet
    4063 #if defined( __nopointer )
    4064     message_string = 'The urban surface module only runs with POINTER version'
    4065     CALL message( 'urban_surface_mod', 'PA0452', 1, 2, 0, 6, 0 )
    4066 #endif
    40673921
    40683922        CALL cpu_log( log_point_s(78), 'usm_init', 'start' )
     
    51755029!--         At horizontal surfaces. Please note, t_surf_wall_h is defined on a
    51765030!--         different data type, but with the same dimension.
    5177 #if ! defined( __nopointer )
    51785031            DO  m = 1, surf_usm_h%ns
    51795032               i = surf_usm_h%i(m)           
     
    52005053               ENDDO
    52015054            ENDDO
    5202 #endif
     5055
    52035056!
    52045057!--         For the sake of correct initialization, set also q_surface.
     
    64166269         
    64176270             CASE ( 't_surf_wall_h' )
    6418 #if defined( __nopointer )                   
    6419                 IF ( k == 1 )  THEN
    6420                    IF ( .NOT.  ALLOCATED( t_surf_wall_h ) )                         &
    6421                       ALLOCATE( t_surf_wall_h(1:surf_usm_h%ns) )
    6422                    READ ( 13 )  tmp_surf_wall_h
    6423                 ENDIF
    6424                 CALL surface_restore_elements(                                 &
    6425                                         t_surf_wall_h, tmp_surf_wall_h,                  &
    6426                                         surf_usm_h%start_index,                & 
    6427                                         start_index_on_file,                   &
    6428                                         end_index_on_file,                     &
    6429                                         nxlc, nysc,                            &
    6430                                         nxlf, nxrf, nysf, nynf,                &
    6431                                         nys_on_file, nyn_on_file,              &
    6432                                         nxl_on_file,nxr_on_file )
    6433 #else                 
    64346271                IF ( k == 1 )  THEN
    64356272                   IF ( .NOT.  ALLOCATED( t_surf_wall_h_1 ) )                       &
     
    64466283                                        nys_on_file, nyn_on_file,              &
    64476284                                        nxl_on_file,nxr_on_file )
    6448 #endif
    64496285
    64506286             CASE ( 't_surf_wall_v(0)' )
    6451 #if defined( __nopointer )           
    6452                 IF ( k == 1 )  THEN
    6453                    IF ( .NOT.  ALLOCATED( t_surf_wall_v(0)%t ) )                    &
    6454                       ALLOCATE( t_surf_wall_v(0)%t(1:surf_usm_v(0)%ns) )
    6455                    READ ( 13 )  tmp_surf_wall_v(0)%t
    6456                 ENDIF
    6457                 CALL surface_restore_elements(                                 &
    6458                                         t_surf_wall_v(0)%t, tmp_surf_wall_v(0)%t,        &
    6459                                         surf_usm_v(0)%start_index,             &
    6460                                         start_index_on_file,                   &
    6461                                         end_index_on_file,                     &
    6462                                         nxlc, nysc,                            &
    6463                                         nxlf, nxrf, nysf, nynf,                &
    6464                                         nys_on_file, nyn_on_file,              &
    6465                                         nxl_on_file,nxr_on_file )
    6466 #else                     
    64676287                IF ( k == 1 )  THEN
    64686288                   IF ( .NOT.  ALLOCATED( t_surf_wall_v_1(0)%t ) )                  &
     
    64796299                                        nys_on_file, nyn_on_file,              &
    64806300                                        nxl_on_file,nxr_on_file )
    6481 #endif
    64826301                     
    64836302             CASE ( 't_surf_wall_v(1)' )
    6484 #if defined( __nopointer )       
    6485                 IF ( k == 1 )  THEN
    6486                    IF ( .NOT.  ALLOCATED( t_surf_wall_v(1)%t ) )                    &
    6487                       ALLOCATE( t_surf_wall_v(1)%t(1:surf_usm_v(1)%ns) )
    6488                    READ ( 13 )  tmp_surf_wall_v(1)%t
    6489                 ENDIF
    6490                 CALL surface_restore_elements(                                 &
    6491                                         t_surf_wall_v(1)%t, tmp_surf_wall_v(1)%t,        &
    6492                                         surf_usm_v(1)%start_index,             &
    6493                                         start_index_on_file,                   &
    6494                                         end_index_on_file,                     &
    6495                                         nxlc, nysc,                            &
    6496                                         nxlf, nxrf, nysf, nynf,                &
    6497                                         nys_on_file, nyn_on_file,              &
    6498                                         nxl_on_file,nxr_on_file )                 
    6499 #else                     
    65006303                IF ( k == 1 )  THEN
    65016304                   IF ( .NOT.  ALLOCATED( t_surf_wall_v_1(1)%t ) )                  &
     
    65126315                                        nys_on_file, nyn_on_file,              &
    65136316                                        nxl_on_file,nxr_on_file )
    6514 #endif
    65156317
    65166318             CASE ( 't_surf_wall_v(2)' )
    6517 #if defined( __nopointer )         
    6518                 IF ( k == 1 )  THEN
    6519                    IF ( .NOT.  ALLOCATED( t_surf_wall_v(2)%t ) )                    &
    6520                       ALLOCATE( t_surf_wall_v(2)%t(1:surf_usm_v(2)%ns) )
    6521                    READ ( 13 )  tmp_surf_wall_v(2)%t
    6522                 ENDIF
    6523                 CALL surface_restore_elements(                                 &
    6524                                         t_surf_wall_v(2)%t, tmp_surf_wall_v(2)%t,        &
    6525                                         surf_usm_v(2)%start_index,             &
    6526                                         start_index_on_file,                   &
    6527                                         end_index_on_file,                     &
    6528                                         nxlc, nysc,                            &
    6529                                         nxlf, nxrf, nysf, nynf,                &
    6530                                         nys_on_file, nyn_on_file,              &
    6531                                         nxl_on_file,nxr_on_file )
    6532 #else                     
    65336319                IF ( k == 1 )  THEN
    65346320                   IF ( .NOT.  ALLOCATED( t_surf_wall_v_1(2)%t ) )                  &
     
    65456331                                        nys_on_file, nyn_on_file,              &
    65466332                                        nxl_on_file,nxr_on_file )
    6547 #endif
    65486333                     
    65496334             CASE ( 't_surf_wall_v(3)' )
    6550 #if defined( __nopointer )   
    6551                 IF ( k == 1 )  THEN
    6552                    IF ( .NOT.  ALLOCATED( t_surf_wall_v(3)%t ) )                    &
    6553                       ALLOCATE( t_surf_wall_v(3)%t(1:surf_usm_v(3)%ns) )
    6554                    READ ( 13 )  tmp_surf_wall_v(3)%t
    6555                 ENDIF
    6556                 CALL surface_restore_elements(                                 &
    6557                                         t_surf_wall_v(3)%t, tmp_surf_wall_v(3)%t,        &
    6558                                         surf_usm_v(3)%start_index,             &
    6559                                         start_index_on_file,                   &
    6560                                         end_index_on_file,                     &
    6561                                         nxlc, nysc,                            &
    6562                                         nxlf, nxrf, nysf, nynf,                &
    6563                                         nys_on_file, nyn_on_file,              &
    6564                                         nxl_on_file,nxr_on_file )
    6565 #else                     
    65666335                IF ( k == 1 )  THEN
    65676336                   IF ( .NOT.  ALLOCATED( t_surf_wall_v_1(3)%t ) )                  &
     
    65786347                                        nys_on_file, nyn_on_file,              &
    65796348                                        nxl_on_file,nxr_on_file )
    6580 #endif
     6349
    65816350             CASE ( 't_surf_green_h' )
    6582 #if defined( __nopointer )                   
    6583                 IF ( k == 1 )  THEN
    6584                    IF ( .NOT.  ALLOCATED( t_surf_green_h ) )                   &
    6585                       ALLOCATE( t_surf_green_h(1:surf_usm_h%ns) )
    6586                    READ ( 13 )  tmp_surf_green_h
    6587                 ENDIF
    6588                 CALL surface_restore_elements(                                 &
    6589                                         t_surf_green_h, tmp_surf_green_h,      &
    6590                                         surf_usm_h%start_index,                &
    6591                                         start_index_on_file,                   &
    6592                                         end_index_on_file,                     &
    6593                                         nxlc, nysc,                            &
    6594                                         nxlf, nxrf, nysf, nynf,                &
    6595                                         nys_on_file, nyn_on_file,              &
    6596                                         nxl_on_file,nxr_on_file )
    6597 #else                     
    65986351                IF ( k == 1 )  THEN
    65996352                   IF ( .NOT.  ALLOCATED( t_surf_green_h_1 ) )                 &
     
    66106363                                        nys_on_file, nyn_on_file,              &
    66116364                                        nxl_on_file,nxr_on_file )
    6612 #endif
    66136365
    66146366             CASE ( 't_surf_green_v(0)' )
    6615 #if defined( __nopointer )           
    6616                 IF ( k == 1 )  THEN
    6617                    IF ( .NOT.  ALLOCATED( t_surf_green_v(0)%t ) )              &
    6618                       ALLOCATE( t_surf_green_v(0)%t(1:surf_usm_v(0)%ns) )
    6619                    READ ( 13 )  tmp_surf_green_v(0)%t
    6620                 ENDIF
    6621                 CALL surface_restore_elements(                                 &
    6622                                         t_surf_green_v(0)%t,                   &
    6623                                         tmp_surf_green_v(0)%t,                 &
    6624                                         surf_usm_v(0)%start_index,             &
    6625                                         start_index_on_file,                   &
    6626                                         end_index_on_file,                     &
    6627                                         nxlc, nysc,                            &
    6628                                         nxlf, nxrf, nysf, nynf,                &
    6629                                         nys_on_file, nyn_on_file,              &
    6630                                         nxl_on_file,nxr_on_file )
    6631 #else                     
    66326367                IF ( k == 1 )  THEN
    66336368                   IF ( .NOT.  ALLOCATED( t_surf_green_v_1(0)%t ) )            &
     
    66456380                                        nys_on_file, nyn_on_file,              &
    66466381                                        nxl_on_file,nxr_on_file )
    6647 #endif
    66486382                   
    66496383             CASE ( 't_surf_green_v(1)' )
    6650 #if defined( __nopointer )       
    6651                 IF ( k == 1 )  THEN
    6652                    IF ( .NOT.  ALLOCATED( t_surf_green_v(1)%t ) )              &
    6653                       ALLOCATE( t_surf_green_v(1)%t(1:surf_usm_v(1)%ns) )
    6654                    READ ( 13 )  tmp_surf_green_v(1)%t
    6655                 ENDIF
    6656                 CALL surface_restore_elements(                                 &
    6657                                         t_surf_green_v(1)%t,                   &
    6658                                         tmp_surf_green_v(1)%t,                 &
    6659                                         surf_usm_v(1)%start_index,             &
    6660                                         start_index_on_file,                   &
    6661                                         end_index_on_file,                     &
    6662                                         nxlc, nysc,                            &
    6663                                         nxlf, nxrf, nysf, nynf,                &
    6664                                         nys_on_file, nyn_on_file,              &
    6665                                         nxl_on_file,nxr_on_file )                 
    6666 #else                     
    66676384                IF ( k == 1 )  THEN
    66686385                   IF ( .NOT.  ALLOCATED( t_surf_green_v_1(1)%t ) )            &
     
    66806397                                        nys_on_file, nyn_on_file,              &
    66816398                                        nxl_on_file,nxr_on_file )
    6682 #endif
    66836399
    66846400             CASE ( 't_surf_green_v(2)' )
    6685 #if defined( __nopointer )         
    6686                 IF ( k == 1 )  THEN
    6687                    IF ( .NOT.  ALLOCATED( t_surf_green_v(2)%t ) )              &
    6688                       ALLOCATE( t_surf_green_v(2)%t(1:surf_usm_v(2)%ns) )
    6689                    READ ( 13 )  tmp_surf_green_v(2)%t
    6690                 ENDIF
    6691                 CALL surface_restore_elements(                                 &
    6692                                         t_surf_green_v(2)%t,                   &
    6693                                         tmp_surf_green_v(2)%t,                 &
    6694                                         surf_usm_v(2)%start_index,             &
    6695                                         start_index_on_file,                   &
    6696                                         end_index_on_file,                     &
    6697                                         nxlc, nysc,                            &
    6698                                         nxlf, nxrf, nysf, nynf,                &
    6699                                         nys_on_file, nyn_on_file,              &
    6700                                         nxl_on_file,nxr_on_file )
    6701 #else                     
    67026401                IF ( k == 1 )  THEN
    67036402                   IF ( .NOT.  ALLOCATED( t_surf_green_v_1(2)%t ) )            &
     
    67156414                                        nys_on_file, nyn_on_file,              &
    67166415                                        nxl_on_file,nxr_on_file )
    6717 #endif
    67186416                   
    67196417             CASE ( 't_surf_green_v(3)' )
    6720 #if defined( __nopointer )   
    6721                 IF ( k == 1 )  THEN
    6722                    IF ( .NOT.  ALLOCATED( t_surf_green_v(3)%t ) )              &
    6723                       ALLOCATE( t_surf_green_v(3)%t(1:surf_usm_v(3)%ns) )
    6724                    READ ( 13 )  tmp_surf_green_v(3)%t
    6725                 ENDIF
    6726                 CALL surface_restore_elements(                                 &
    6727                                         t_surf_green_v(3)%t,                   &
    6728                                         tmp_surf_green_v(3)%t,                 &
    6729                                         surf_usm_v(3)%start_index,             &
    6730                                         start_index_on_file,                   &
    6731                                         end_index_on_file,                     &
    6732                                         nxlc, nysc,                            &
    6733                                         nxlf, nxrf, nysf, nynf,                &
    6734                                         nys_on_file, nyn_on_file,              &
    6735                                         nxl_on_file,nxr_on_file )
    6736 #else                     
    67376418                IF ( k == 1 )  THEN
    67386419                   IF ( .NOT.  ALLOCATED( t_surf_green_v_1(3)%t ) )            &
     
    67506431                                        nys_on_file, nyn_on_file,              &
    67516432                                        nxl_on_file,nxr_on_file )
    6752 #endif
     6433
    67536434             CASE ( 't_surf_window_h' )
    6754 #if defined( __nopointer )                   
    6755                 IF ( k == 1 )  THEN
    6756                    IF ( .NOT.  ALLOCATED( t_surf_window_h ) )                  &
    6757                       ALLOCATE( t_surf_window_h(1:surf_usm_h%ns) )
    6758                    READ ( 13 )  tmp_surf_window_h
    6759                 ENDIF
    6760                 CALL surface_restore_elements(                                 &
    6761                                         t_surf_window_h, tmp_surf_window_h,    &
    6762                                         surf_usm_h%start_index,                &
    6763                                         start_index_on_file,                   &
    6764                                         end_index_on_file,                     &
    6765                                         nxlc, nysc,                            &
    6766                                         nxlf, nxrf, nysf, nynf,                &
    6767                                         nys_on_file, nyn_on_file,              &
    6768                                         nxl_on_file,nxr_on_file )
    6769 #else                     
    67706435                IF ( k == 1 )  THEN
    67716436                   IF ( .NOT.  ALLOCATED( t_surf_window_h_1 ) )                &
     
    67836448                                        nys_on_file, nyn_on_file,              &
    67846449                                        nxl_on_file,nxr_on_file )
    6785 #endif
    67866450
    67876451             CASE ( 't_surf_window_v(0)' )
    6788 #if defined( __nopointer )           
    6789                 IF ( k == 1 )  THEN
    6790                    IF ( .NOT.  ALLOCATED( t_surf_window_v(0)%t ) )             &
    6791                       ALLOCATE( t_surf_window_v(0)%t(1:surf_usm_v(0)%ns) )
    6792                    READ ( 13 )  tmp_surf_window_v(0)%t
    6793                 ENDIF
    6794                 CALL surface_restore_elements(                                 &
    6795                                         t_surf_window_v(0)%t,                  &
    6796                                         tmp_surf_window_v(0)%t,                &
    6797                                         surf_usm_v(0)%start_index,             &
    6798                                         start_index_on_file,                   &
    6799                                         end_index_on_file,                     &
    6800                                         nxlc, nysc,                            &
    6801                                         nxlf, nxrf, nysf, nynf,                &
    6802                                         nys_on_file, nyn_on_file,              &
    6803                                         nxl_on_file,nxr_on_file )
    6804 #else                     
    68056452                IF ( k == 1 )  THEN
    68066453                   IF ( .NOT.  ALLOCATED( t_surf_window_v_1(0)%t ) )           &
     
    68186465                                        nys_on_file, nyn_on_file,              &
    68196466                                        nxl_on_file,nxr_on_file )
    6820 #endif
    68216467                   
    68226468             CASE ( 't_surf_window_v(1)' )
    6823 #if defined( __nopointer )       
    6824                 IF ( k == 1 )  THEN
    6825                    IF ( .NOT.  ALLOCATED( t_surf_window_v(1)%t ) )             &
    6826                       ALLOCATE( t_surf_window_v(1)%t(1:surf_usm_v(1)%ns) )
    6827                    READ ( 13 )  tmp_surf_window_v(1)%t
    6828                 ENDIF
    6829                 CALL surface_restore_elements(                                 &
    6830                                         t_surf_window_v(1)%t,                  &
    6831                                         tmp_surf_window_v(1)%t,                &
    6832                                         surf_usm_v(1)%start_index,             &
    6833                                         start_index_on_file,                   &
    6834                                         end_index_on_file,                     &
    6835                                         nxlc, nysc,                            &
    6836                                         nxlf, nxrf, nysf, nynf,                &
    6837                                         nys_on_file, nyn_on_file,              &
    6838                                         nxl_on_file,nxr_on_file )                 
    6839 #else                     
    68406469                IF ( k == 1 )  THEN
    68416470                   IF ( .NOT.  ALLOCATED( t_surf_window_v_1(1)%t ) )           &
     
    68536482                                        nys_on_file, nyn_on_file,              &
    68546483                                        nxl_on_file,nxr_on_file )
    6855 #endif
    68566484
    68576485             CASE ( 't_surf_window_v(2)' )
    6858 #if defined( __nopointer )         
    6859                 IF ( k == 1 )  THEN
    6860                    IF ( .NOT.  ALLOCATED( t_surf_window_v(2)%t ) )             &
    6861                       ALLOCATE( t_surf_window_v(2)%t(1:surf_usm_v(2)%ns) )
    6862                    READ ( 13 )  tmp_surf_window_v(2)%t
    6863                 ENDIF
    6864                 CALL surface_restore_elements(                                 &
    6865                                         t_surf_window_v(2)%t,                  &
    6866                                         tmp_surf_window_v(2)%t,                &
    6867                                         surf_usm_v(2)%start_index,             &   
    6868                                         start_index_on_file,                   &
    6869                                         end_index_on_file,                     &
    6870                                         nxlc, nysc,                            &
    6871                                         nxlf, nxrf, nysf, nynf,                &
    6872                                         nys_on_file, nyn_on_file,              &
    6873                                         nxl_on_file,nxr_on_file )
    6874 #else                     
    68756486                IF ( k == 1 )  THEN
    68766487                   IF ( .NOT.  ALLOCATED( t_surf_window_v_1(2)%t ) )           &
     
    68886499                                        nys_on_file, nyn_on_file,              &
    68896500                                        nxl_on_file,nxr_on_file )
    6890 #endif
    68916501                   
    68926502             CASE ( 't_surf_window_v(3)' )
    6893 #if defined( __nopointer )   
    6894                 IF ( k == 1 )  THEN
    6895                    IF ( .NOT.  ALLOCATED( t_surf_window_v(3)%t ) )             &
    6896                       ALLOCATE( t_surf_window_v(3)%t(1:surf_usm_v(3)%ns) )
    6897                    READ ( 13 )  tmp_surf_window_v(3)%t
    6898                 ENDIF
    6899                 CALL surface_restore_elements(                                 &
    6900                                         t_surf_window_v(3)%t,                  &
    6901                                         tmp_surf_window_v(3)%t,                &
    6902                                         surf_usm_v(3)%start_index,             &
    6903                                         start_index_on_file,                   &
    6904                                         end_index_on_file,                     &
    6905                                         nxlc, nysc,                            &
    6906                                         nxlf, nxrf, nysf, nynf,                &
    6907                                         nys_on_file, nyn_on_file,              &
    6908                                         nxl_on_file,nxr_on_file )
    6909 #else                     
    69106503                IF ( k == 1 )  THEN
    69116504                   IF ( .NOT.  ALLOCATED( t_surf_window_v_1(3)%t ) )           &
     
    69236516                                        nys_on_file, nyn_on_file,              &
    69246517                                        nxl_on_file,nxr_on_file )
    6925 #endif
     6518
    69266519             CASE ( 't_wall_h' )
    6927 #if defined( __nopointer )
    6928                 IF ( k == 1 )  THEN
    6929                    IF ( .NOT.  ALLOCATED( t_wall_h ) )                         &
    6930                       ALLOCATE( t_wall_h(nzb_wall:nzt_wall+1,1:surf_usm_h%ns) )
    6931                    READ ( 13 )  tmp_wall_h
    6932                 ENDIF
    6933                 CALL surface_restore_elements(                                 &
    6934                                         t_wall_h, tmp_wall_h,                  &
    6935                                         surf_usm_h%start_index,                &
    6936                                         start_index_on_file,                   &
    6937                                         end_index_on_file,                     &
    6938                                         nxlc, nysc,                            &
    6939                                         nxlf, nxrf, nysf, nynf,                &
    6940                                         nys_on_file, nyn_on_file,              &
    6941                                         nxl_on_file,nxr_on_file )
    6942 #else
    69436520                IF ( k == 1 )  THEN
    69446521                   IF ( .NOT.  ALLOCATED( t_wall_h_1 ) )                       &
     
    69566533                                        nys_on_file, nyn_on_file,              &
    69576534                                        nxl_on_file,nxr_on_file )
    6958 #endif
     6535
    69596536             CASE ( 't_wall_v(0)' )
    6960 #if defined( __nopointer )
    6961                 IF ( k == 1 )  THEN
    6962                    IF ( .NOT.  ALLOCATED( t_wall_v(0)%t ) )                    &
    6963                       ALLOCATE( t_wall_v(0)%t(nzb_wall:nzt_wall+1,             &
    6964                                               1:surf_usm_v(0)%ns) )
    6965                    READ ( 13 )  tmp_wall_v(0)%t
    6966                 ENDIF
    6967                 CALL surface_restore_elements(                                 &
    6968                                         t_wall_v(0)%t, tmp_wall_v(0)%t,        &
    6969                                         surf_usm_v(0)%start_index,             &   
    6970                                         start_index_on_file,                   &
    6971                                         end_index_on_file,                     &
    6972                                         nxlc, nysc,                            &
    6973                                         nxlf, nxrf, nysf, nynf,                &
    6974                                         nys_on_file, nyn_on_file,              &
    6975                                         nxl_on_file,nxr_on_file )
    6976 #else
    69776537                IF ( k == 1 )  THEN
    69786538                   IF ( .NOT.  ALLOCATED( t_wall_v_1(0)%t ) )                  &
     
    69906550                                        nys_on_file, nyn_on_file,              &
    69916551                                        nxl_on_file,nxr_on_file )
    6992 #endif
     6552
    69936553             CASE ( 't_wall_v(1)' )
    6994 #if defined( __nopointer )
    6995                 IF ( k == 1 )  THEN
    6996                    IF ( .NOT.  ALLOCATED( t_wall_v(1)%t ) )                    &
    6997                       ALLOCATE( t_wall_v(1)%t(nzb_wall:nzt_wall+1,             &
    6998                                               1:surf_usm_v(1)%ns) )
    6999                    READ ( 13 )  tmp_wall_v(1)%t
    7000                 ENDIF
    7001                 CALL surface_restore_elements(                                 &
    7002                                         t_wall_v(1)%t, tmp_wall_v(1)%t,        &
    7003                                         surf_usm_v(1)%start_index,             &
    7004                                         start_index_on_file,                   &
    7005                                         end_index_on_file ,                    &
    7006                                         nxlc, nysc,                            &
    7007                                         nxlf, nxrf, nysf, nynf,                &
    7008                                         nys_on_file, nyn_on_file,              &
    7009                                         nxl_on_file, nxr_on_file )
    7010 #else
    70116554                IF ( k == 1 )  THEN
    70126555                   IF ( .NOT.  ALLOCATED( t_wall_v_1(1)%t ) )                  &
     
    70246567                                        nys_on_file, nyn_on_file,              &
    70256568                                        nxl_on_file,nxr_on_file )
    7026 #endif
     6569
    70276570             CASE ( 't_wall_v(2)' )
    7028 #if defined( __nopointer )
    7029                 IF ( k == 1 )  THEN
    7030                    IF ( .NOT.  ALLOCATED( t_wall_v(2)%t ) )                    &
    7031                       ALLOCATE( t_wall_v(2)%t(nzb_wall:nzt_wall+1,             &
    7032                                               1:surf_usm_v(2)%ns) )
    7033                    READ ( 13 )  tmp_wall_v(2)%t
    7034                 ENDIF
    7035                 CALL surface_restore_elements(                                 &
    7036                                         t_wall_v(2)%t, tmp_wall_v(2)%t,        &
    7037                                         surf_usm_v(2)%start_index,             & 
    7038                                         start_index_on_file,                   &
    7039                                         end_index_on_file,                     &
    7040                                         nxlc, nysc,                            &
    7041                                         nxlf, nxrf, nysf, nynf,                &
    7042                                         nys_on_file, nyn_on_file,              &
    7043                                         nxl_on_file,nxr_on_file )
    7044 #else
    70456571                IF ( k == 1 )  THEN
    70466572                   IF ( .NOT.  ALLOCATED( t_wall_v_1(2)%t ) )                  &
     
    70586584                                        nys_on_file, nyn_on_file,              &
    70596585                                        nxl_on_file,nxr_on_file )
    7060 #endif
     6586
    70616587             CASE ( 't_wall_v(3)' )
    7062 #if defined( __nopointer )
    7063                 IF ( k == 1 )  THEN
    7064                    IF ( .NOT.  ALLOCATED( t_wall_v(3)%t ) )                    &
    7065                       ALLOCATE( t_wall_v(3)%t(nzb_wall:nzt_wall+1,             &
    7066                                               1:surf_usm_v(3)%ns) )
    7067                    READ ( 13 )  tmp_wall_v(3)%t
    7068                 ENDIF
    7069                 CALL surface_restore_elements(                                 &
    7070                                         t_wall_v(3)%t, tmp_wall_v(3)%t,        &
    7071                                         surf_usm_v(3)%start_index,             &   
    7072                                         start_index_on_file,                   &
    7073                                         end_index_on_file,                     &
    7074                                         nxlc, nysc,                            &
    7075                                         nxlf, nxrf, nysf, nynf,                &
    7076                                         nys_on_file, nyn_on_file,              &
    7077                                         nxl_on_file,nxr_on_file )
    7078 #else
    70796588                IF ( k == 1 )  THEN
    70806589                   IF ( .NOT.  ALLOCATED( t_wall_v_1(3)%t ) )                  &
     
    70926601                                        nys_on_file, nyn_on_file,              &
    70936602                                        nxl_on_file,nxr_on_file )
    7094 #endif
     6603
    70956604             CASE ( 't_green_h' )
    7096 #if defined( __nopointer )
    7097                 IF ( k == 1 )  THEN
    7098                    IF ( .NOT.  ALLOCATED( t_green_h ) )                        &
    7099                       ALLOCATE( t_green_h(nzb_wall:nzt_wall+1,                 &
    7100                                           1:surf_usm_h%ns) )
    7101                    READ ( 13 )  tmp_green_h
    7102                 ENDIF
    7103                 CALL surface_restore_elements(                                 &
    7104                                         t_green_h, tmp_green_h,                &
    7105                                         surf_usm_h%start_index,                &
    7106                                         start_index_on_file,                   &
    7107                                         end_index_on_file,                     &
    7108                                         nxlc, nysc,                            &
    7109                                         nxlf, nxrf, nysf, nynf,                &
    7110                                         nys_on_file, nyn_on_file,              &
    7111                                         nxl_on_file,nxr_on_file )
    7112 #else
    71136605                IF ( k == 1 )  THEN
    71146606                   IF ( .NOT.  ALLOCATED( t_green_h_1 ) )                      &
     
    71266618                                        nys_on_file, nyn_on_file,              &
    71276619                                        nxl_on_file,nxr_on_file )
    7128 #endif
     6620
    71296621             CASE ( 't_green_v(0)' )
    7130 #if defined( __nopointer )
    7131                 IF ( k == 1 )  THEN
    7132                    IF ( .NOT.  ALLOCATED( t_green_v(0)%t ) )                   &
    7133                       ALLOCATE( t_green_v(0)%t(nzb_wall:nzt_wall+1,            &
    7134                                                1:surf_usm_v(0)%ns) )
    7135                    READ ( 13 )  tmp_green_v(0)%t
    7136                 ENDIF
    7137                 CALL surface_restore_elements(                                 &
    7138                                         t_green_v(0)%t, tmp_green_v(0)%t,      &
    7139                                         surf_usm_v(0)%start_index,             &
    7140                                         start_index_on_file,                   &
    7141                                         end_index_on_file,                     &
    7142                                         nxlc, nysc,                            &
    7143                                         nxlf, nxrf, nysf, nynf,                &
    7144                                         nys_on_file, nyn_on_file,              &
    7145                                         nxl_on_file,nxr_on_file )
    7146 #else
    71476622                IF ( k == 1 )  THEN
    71486623                   IF ( .NOT.  ALLOCATED( t_green_v_1(0)%t ) )                 &
     
    71606635                                        nys_on_file, nyn_on_file,              &
    71616636                                        nxl_on_file,nxr_on_file )
    7162 #endif
     6637
    71636638             CASE ( 't_green_v(1)' )
    7164 #if defined( __nopointer )
    7165                 IF ( k == 1 )  THEN
    7166                    IF ( .NOT.  ALLOCATED( t_green_v(1)%t ) )                   &
    7167                       ALLOCATE( t_green_v(1)%t(nzb_wall:nzt_wall+1,            &
    7168                                                1:surf_usm_v(1)%ns) )
    7169                    READ ( 13 )  tmp_green_v(1)%t
    7170                 ENDIF
    7171                 CALL surface_restore_elements(                                 &
    7172                                         t_green_v(1)%t, tmp_green_v(1)%t,      &
    7173                                         surf_usm_v(1)%start_index,             &
    7174                                         start_index_on_file,                   &
    7175                                         end_index_on_file ,                    &
    7176                                         nxlc, nysc,                            &
    7177                                         nxlf, nxrf, nysf, nynf,                &
    7178                                         nys_on_file, nyn_on_file,              &
    7179                                         nxl_on_file,nxr_on_file )
    7180 #else
    71816639                IF ( k == 1 )  THEN
    71826640                   IF ( .NOT.  ALLOCATED( t_green_v_1(1)%t ) )                 &
     
    71946652                                        nys_on_file, nyn_on_file,              &
    71956653                                        nxl_on_file,nxr_on_file )
    7196 #endif
     6654
    71976655             CASE ( 't_green_v(2)' )
    7198 #if defined( __nopointer )
    7199                 IF ( k == 1 )  THEN
    7200                    IF ( .NOT.  ALLOCATED( t_green_v(2)%t ) )                   &
    7201                       ALLOCATE( t_green_v(2)%t(nzb_wall:nzt_wall+1,            &
    7202                                                1:surf_usm_v(2)%ns) )
    7203                    READ ( 13 )  tmp_green_v(2)%t
    7204                 ENDIF
    7205                 CALL surface_restore_elements(                                 &
    7206                                         t_green_v(2)%t, tmp_green_v(2)%t,      &
    7207                                         surf_usm_v(2)%start_index,             &
    7208                                         start_index_on_file,                   &
    7209                                         end_index_on_file,                     &
    7210                                         nxlc, nysc,                            &
    7211                                         nxlf, nxrf, nysf, nynf,                &
    7212                                         nys_on_file, nyn_on_file,              &
    7213                                         nxl_on_file,nxr_on_file )
    7214 #else
    72156656                IF ( k == 1 )  THEN
    72166657                   IF ( .NOT.  ALLOCATED( t_green_v_1(2)%t ) )                 &
     
    72286669                                        nys_on_file, nyn_on_file,              &
    72296670                                        nxl_on_file,nxr_on_file )
    7230 #endif
     6671
    72316672             CASE ( 't_green_v(3)' )
    7232 #if defined( __nopointer )
    7233                 IF ( k == 1 )  THEN
    7234                    IF ( .NOT.  ALLOCATED( t_green_v(3)%t ) )                   &
    7235                       ALLOCATE( t_green_v(3)%t(nzb_wall:nzt_wall+1,            &
    7236                                                1:surf_usm_v(3)%ns) )
    7237                    READ ( 13 )  tmp_green_v(3)%t
    7238                 ENDIF
    7239                 CALL surface_restore_elements(                                 &
    7240                                         t_green_v(3)%t, tmp_green_v(3)%t,      &
    7241                                         surf_usm_v(3)%start_index,             & 
    7242                                         start_index_on_file,                   &
    7243                                         end_index_on_file,                     &
    7244                                         nxlc, nysc,                            &
    7245                                         nxlf, nxrf, nysf, nynf,                &
    7246                                         nys_on_file, nyn_on_file,              &
    7247                                         nxl_on_file,nxr_on_file )
    7248 #else
    72496673                IF ( k == 1 )  THEN
    72506674                   IF ( .NOT.  ALLOCATED( t_green_v_1(3)%t ) )                 &
     
    72626686                                        nys_on_file, nyn_on_file,              &
    72636687                                        nxl_on_file,nxr_on_file )
    7264 #endif
     6688
    72656689             CASE ( 't_window_h' )
    7266 #if defined( __nopointer )
    7267                 IF ( k == 1 )  THEN
    7268                    IF ( .NOT.  ALLOCATED( t_window_h ) )                       &
    7269                       ALLOCATE( t_window_h(nzb_wall:nzt_wall+1,                &
    7270                                            1:surf_usm_h%ns) )
    7271                    READ ( 13 )  tmp_window_h
    7272                 ENDIF
    7273                 CALL surface_restore_elements(                                 &
    7274                                         t_window_h, tmp_window_h,              &
    7275                                         surf_usm_h%start_index,                &
    7276                                         start_index_on_file,                   &
    7277                                         end_index_on_file,                     &
    7278                                         nxlc, nysc,                            &
    7279                                         nxlf, nxrf, nysf, nynf,                &
    7280                                         nys_on_file, nyn_on_file,              &
    7281                                         nxl_on_file,nxr_on_file )
    7282 #else
    72836690                IF ( k == 1 )  THEN
    72846691                   IF ( .NOT.  ALLOCATED( t_window_h_1 ) )                     &
     
    72966703                                        nys_on_file, nyn_on_file,              &
    72976704                                        nxl_on_file, nxr_on_file )
    7298 #endif
     6705
    72996706             CASE ( 't_window_v(0)' )
    7300 #if defined( __nopointer )
    7301                 IF ( k == 1 )  THEN
    7302                    IF ( .NOT.  ALLOCATED( t_window_v(0)%t ) )                  &
    7303                       ALLOCATE( t_window_v(0)%t(nzb_wall:nzt_wall+1,           &
    7304                                                 1:surf_usm_v(0)%ns) )
    7305                    READ ( 13 )  tmp_window_v(0)%t
    7306                 ENDIF
    7307                 CALL surface_restore_elements(                                 &
    7308                                         t_window_v(0)%t, tmp_window_v(0)%t,    &
    7309                                         surf_usm_v(0)%start_index,             &
    7310                                         start_index_on_file,                   &
    7311                                         end_index_on_file,                     &
    7312                                         nxlc, nysc,                            &
    7313                                         nxlf, nxrf, nysf, nynf,                &
    7314                                         nys_on_file, nyn_on_file,              &
    7315                                         nxl_on_file, nxr_on_file )
    7316 #else
    73176707                IF ( k == 1 )  THEN
    73186708                   IF ( .NOT.  ALLOCATED( t_window_v_1(0)%t ) )                &
     
    73316721                                        nys_on_file, nyn_on_file,              &
    73326722                                        nxl_on_file,nxr_on_file )
    7333 #endif
     6723
    73346724             CASE ( 't_window_v(1)' )
    7335 #if defined( __nopointer )
    7336                 IF ( k == 1 )  THEN
    7337                    IF ( .NOT.  ALLOCATED( t_window_v(1)%t ) )                  &
    7338                       ALLOCATE( t_window_v(1)%t(nzb_wall:nzt_wall+1,           &
    7339                                                 1:surf_usm_v(1)%ns) )
    7340                    READ ( 13 )  tmp_window_v(1)%t
    7341                 ENDIF
    7342                 CALL surface_restore_elements(                                 &
    7343                                         t_window_v(1)%t, tmp_window_v(1)%t,    &
    7344                                         surf_usm_v(1)%start_index,             &
    7345                                         start_index_on_file,                   &
    7346                                         end_index_on_file ,                    &
    7347                                         nxlc, nysc,                            &
    7348                                         nxlf, nxrf, nysf, nynf,                &
    7349                                         nys_on_file, nyn_on_file,              &
    7350                                         nxl_on_file, nxr_on_file )
    7351 #else
    73526725                IF ( k == 1 )  THEN
    73536726                   IF ( .NOT.  ALLOCATED( t_window_v_1(1)%t ) )                &
     
    73666739                                        nys_on_file, nyn_on_file,              &
    73676740                                        nxl_on_file,nxr_on_file )
    7368 #endif
     6741
    73696742             CASE ( 't_window_v(2)' )
    7370 #if defined( __nopointer )
    7371                 IF ( k == 1 )  THEN
    7372                    IF ( .NOT.  ALLOCATED( t_window_v(2)%t ) )                  &
    7373                       ALLOCATE( t_window_v(2)%t(nzb_wall:nzt_wall+1,           &
    7374                                                 1:surf_usm_v(2)%ns) )
    7375                    READ ( 13 )  tmp_window_v(2)%t
    7376                 ENDIF
    7377                 CALL surface_restore_elements(                                 &
    7378                                         t_window_v(2)%t, tmp_window_v(2)%t,    &
    7379                                         surf_usm_v(2)%start_index,             &
    7380                                         start_index_on_file,                   &
    7381                                         end_index_on_file,                     &
    7382                                         nxlc, nysc,                            &
    7383                                         nxlf, nxrf, nysf, nynf,                &
    7384                                         nys_on_file, nyn_on_file,              &
    7385                                         nxl_on_file,nxr_on_file )
    7386 #else
    73876743                IF ( k == 1 )  THEN
    73886744                   IF ( .NOT.  ALLOCATED( t_window_v_1(2)%t ) )                &
     
    74016757                                        nys_on_file, nyn_on_file,              &
    74026758                                        nxl_on_file,nxr_on_file )
    7403 #endif
     6759
    74046760             CASE ( 't_window_v(3)' )
    7405 #if defined( __nopointer )
    7406                 IF ( k == 1 )  THEN
    7407                    IF ( .NOT.  ALLOCATED( t_window_v(3)%t ) )                  &
    7408                       ALLOCATE( t_window_v(3)%t(nzb_wall:nzt_wall+1,           &
    7409                                                 1:surf_usm_v(3)%ns) )
    7410                    READ ( 13 )  tmp_window_v(3)%t
    7411                 ENDIF
    7412                 CALL surface_restore_elements(                                 &
    7413                                         t_window_v(3)%t, tmp_window_v(3)%t,    &
    7414                                         surf_usm_v(3)%start_index,             &
    7415                                         start_index_on_file,                   &
    7416                                         end_index_on_file,                     &
    7417                                         nxlc, nysc,                            &
    7418                                         nxlf, nxrf, nysf, nynf,                &
    7419                                         nys_on_file, nyn_on_file,              &
    7420                                         nxl_on_file,nxr_on_file )
    7421 #else
    74226761                IF ( k == 1 )  THEN
    74236762                   IF ( .NOT.  ALLOCATED( t_window_v_1(3)%t ) )                &
     
    74356774                                        nys_on_file, nyn_on_file,              &
    74366775                                        nxl_on_file,nxr_on_file )
    7437 #endif
     6776
    74386777             CASE DEFAULT
    74396778
     
    76326971
    76336972           IF ( usm_par(5,jw,iw) == 0 )  THEN
    7634 #if ! defined( __nopointer )
     6973
    76356974              IF ( zu(kw) >= roof_height_limit )  THEN
    76366975                 surf_usm_h%isroof_surf(m)   = .TRUE.
     
    76406979                 surf_usm_h%surface_types(m) = land_category         !< default category for land surface
    76416980              ENDIF
    7642 #endif
     6981
    76436982              surf_usm_h%albedo(:,m)    = -1.0_wp
    76446983              surf_usm_h%thickness_wall(m) = -1.0_wp
     
    81887527              lambda_surface_green = surf_usm_h%lambda_surf_green(m)
    81897528           ENDIF
    8190 #if ! defined( __nopointer )
     7529
    81917530!            pt1  = pt(k,j,i)
    81927531           IF ( humidity )  THEN
     
    81997538           rho_cp  = c_p * hyp(k) / ( r_d * surf_usm_h%pt1(m) * exner(k) )
    82007539
    8201 if (surf_usm_h%frac(ind_pav_green,m).gt.0.0_wp) then
    8202 !
    8203 !--         Calculate frequently used parameters
    8204             rho_lv    = rho_cp / c_p * l_v
    8205             drho_l_lv = 1.0_wp / (rho_l * l_v)
    8206 endif
    8207 #endif
     7540           IF ( surf_usm_h%frac(ind_pav_green,m) > 0.0_wp )  THEN
     7541!
     7542!--           Calculate frequently used parameters
     7543              rho_lv    = rho_cp / c_p * l_v
     7544              drho_l_lv = 1.0_wp / (rho_l * l_v)
     7545           ENDIF
     7546
    82087547!
    82097548!--        Calculate aerodyamic resistance.
     
    86377976             lambda_surface_green = surf_usm_v(l)%lambda_surf_green(m)
    86387977
    8639 #if ! defined( __nopointer )         
    86407978!            pt1  = pt(k,j,i)
    86417979           IF ( humidity )  THEN
     
    86487986             rho_cp  = c_p * hyp(k) / ( r_d * surf_usm_v(l)%pt1(m) * exner(k) )
    86497987             
    8650 if (surf_usm_v(l)%frac(1,m).gt.0.0_wp) then
    8651 !
    8652 !--         Calculate frequently used parameters
    8653             rho_lv    = rho_cp / c_p * l_v
    8654             drho_l_lv = 1.0_wp / (rho_l * l_v)
    8655 endif
    8656 #endif
     7988            IF (surf_usm_v(l)%frac(1,m) > 0.0_wp )  THEN
     7989!
     7990!--            Calculate frequently used parameters
     7991               rho_lv    = rho_cp / c_p * l_v
     7992               drho_l_lv = 1.0_wp / (rho_l * l_v)
     7993            ENDIF
    86577994
    86587995!--          Calculation of r_a for vertical surfaces
     
    90538390!--     pt and shf are defined on nxlg:nxrg,nysg:nyng
    90548391!--     get the borders from neighbours
    9055 #if ! defined( __nopointer )
    90568392        CALL exchange_horiz( pt, nbgp )
    9057 #endif
    90588393
    90598394!--     calculation of force_radiation_call:
     
    91888523
    91898524       INTEGER(iwp), INTENT(IN) ::  mod_count
     8525
    91908526     
    9191 #if defined( __nopointer )
    9192        t_surf_wall_h    = t_surf_wall_h_p
    9193        t_wall_h    = t_wall_h_p
    9194        t_surf_wall_v    = t_surf_wall_v_p
    9195        t_wall_v    = t_wall_v_p
    9196        t_surf_window_h    = t_surf_window_h_p
    9197        t_window_h    = t_window_h_p
    9198        t_surf_window_v    = t_surf_window_v_p
    9199        t_window_v    = t_window_v_p
    9200        t_surf_green_h    = t_surf_green_h_p
    9201        t_surf_green_v    = t_surf_green_v_p
    9202        t_green_h    = t_green_h_p
    9203        t_green_v    = t_green_v_p
    9204 #else
    92058527       SELECT CASE ( mod_count )
     8528
    92068529          CASE ( 0 )
    92078530!
     
    92398562             t_green_v     => t_green_v_2;    t_green_v_p     => t_green_v_1
    92408563       END SELECT
    9241 #endif
    92428564       
    92438565    END SUBROUTINE usm_swap_timelevel
Note: See TracChangeset for help on using the changeset viewer.