Ignore:
Timestamp:
Jul 12, 2016 4:34:24 PM (8 years ago)
Author:
suehring
Message:

Separate balance equations for humidity and passive_scalar

File:
1 edited

Legend:

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

    r1852 r1960  
    1919! Current revisions:
    2020! -----------------
    21 !
     21! Scalar surface flux added
     22! Rename INTEGER variable s into s_ind, as s is already assigned to scalar
    2223!
    2324! Former revisions:
     
    138139    USE arrays_3d,                                                             &
    139140        ONLY:  dzw, e, nr, ol, p, pt, precipitation_amount, precipitation_rate,&
    140                prr,q, qc, ql, ql_c, ql_v, ql_vp, qr, qsws, rho, sa, shf, tend, &
    141                ts, u, us, v, vpt, w, z0, z0h, z0q, zu, zw
     141               prr,q, qc, ql, ql_c, ql_v, ql_vp, qr, qsws, rho, s, sa, shf,    &
     142               ssws, tend, ts, u, us, v, vpt, w, z0, z0h, z0q, zu, zw
    142143       
    143144    USE averaging
     
    224225    INTEGER(iwp) ::  nzt_do    !< upper limit of the data field (usually nzt+1)
    225226    INTEGER(iwp) ::  psi       !<
    226     INTEGER(iwp) ::  s         !<
     227    INTEGER(iwp) ::  s_ind     !<
    227228    INTEGER(iwp) ::  sender    !<
    228229    INTEGER(iwp) ::  ind(4)    !<
     
    268269
    269270       CASE ( 'xy' )
    270           s = 1
     271          s_ind = 1
    271272          ALLOCATE( level_z(nzb:nzt+1), local_2d(nxlg:nxrg,nysg:nyng) )
    272273
    273274          IF ( netcdf_data_format > 4 )  THEN
    274275             ns = 1
    275              DO WHILE ( section(ns,s) /= -9999  .AND.  ns <= 100 )
     276             DO WHILE ( section(ns,s_ind) /= -9999  .AND.  ns <= 100 )
    276277                ns = ns + 1
    277278             ENDDO
     
    298299
    299300       CASE ( 'xz' )
    300           s = 2
     301          s_ind = 2
    301302          ALLOCATE( local_2d(nxlg:nxrg,nzb:nzt+1) )
    302303
    303304          IF ( netcdf_data_format > 4 )  THEN
    304305             ns = 1
    305              DO WHILE ( section(ns,s) /= -9999  .AND.  ns <= 100 )
     306             DO WHILE ( section(ns,s_ind) /= -9999  .AND.  ns <= 100 )
    306307                ns = ns + 1
    307308             ENDDO
     
    329330
    330331       CASE ( 'yz' )
    331           s = 3
     332          s_ind = 3
    332333          ALLOCATE( local_2d(nysg:nyng,nzb:nzt+1) )
    333334
    334335          IF ( netcdf_data_format > 4 )  THEN
    335336             ns = 1
    336              DO WHILE ( section(ns,s) /= -9999  .AND.  ns <= 100 )
     337             DO WHILE ( section(ns,s_ind) /= -9999  .AND.  ns <= 100 )
    337338                ns = ns + 1
    338339             ENDDO
     
    10701071             CASE ( 's_xy', 's_xz', 's_yz' )
    10711072                IF ( av == 0 )  THEN
    1072                    to_be_resorted => q
     1073                   to_be_resorted => s
    10731074                ELSE
    10741075                   to_be_resorted => s_av
     
    11171118                two_d = .TRUE.
    11181119                level_z(nzb+1) = zu(nzb+1)
     1120               
     1121             CASE ( 'ssws*_xy' )        ! 2d-array
     1122                IF ( av == 0 ) THEN
     1123                   DO  i = nxlg, nxrg
     1124                      DO  j = nysg, nyng
     1125                         local_pf(i,j,nzb+1) =  ssws(j,i)
     1126                      ENDDO
     1127                   ENDDO
     1128                ELSE
     1129                   DO  i = nxlg, nxrg
     1130                      DO  j = nysg, nyng
     1131                         local_pf(i,j,nzb+1) =  ssws_av(j,i)
     1132                      ENDDO
     1133                   ENDDO
     1134                ENDIF
     1135                resorted = .TRUE.
     1136                two_d = .TRUE.
     1137                level_z(nzb+1) = zu(nzb+1)               
    11191138
    11201139             CASE ( 't*_xy' )        ! 2d-array
     
    13031322!--       section mode chosen.
    13041323          is = 1
    1305    loop1: DO WHILE ( section(is,s) /= -9999  .OR.  two_d )
     1324   loop1: DO WHILE ( section(is,s_ind) /= -9999  .OR.  two_d )
    13061325
    13071326             SELECT CASE ( mode )
     
    13131332                      layer_xy = nzb+1
    13141333                   ELSE
    1315                       layer_xy = section(is,s)
     1334                      layer_xy = section(is,s_ind)
    13161335                   ENDIF
    13171336
     
    13471366!
    13481367!--                If required, carry out averaging along z
    1349                    IF ( section(is,s) == -1  .AND.  .NOT. two_d )  THEN
     1368                   IF ( section(is,s_ind) == -1  .AND.  .NOT. two_d )  THEN
    13501369
    13511370                      local_2d = 0.0_wp
     
    15371556!
    15381557!--                If required, carry out averaging along y
    1539                    IF ( section(is,s) == -1 )  THEN
     1558                   IF ( section(is,s_ind) == -1 )  THEN
    15401559
    15411560                      ALLOCATE( local_2d_l(nxlg:nxrg,nzb_do:nzt_do) )
     
    15701589!--                   Just store the respective section on the local array
    15711590!--                   (but only if it is available on this PE!)
    1572                       IF ( section(is,s) >= nys  .AND.  section(is,s) <= nyn ) &
     1591                      IF ( section(is,s_ind) >= nys  .AND.  section(is,s_ind) <= nyn ) &
    15731592                      THEN
    1574                          local_2d = local_pf(:,section(is,s),nzb_do:nzt_do)
     1593                         local_2d = local_pf(:,section(is,s_ind),nzb_do:nzt_do)
    15751594                      ENDIF
    15761595
     
    15841603!--                   sections reside. Cross sections averaged along y are
    15851604!--                   output on the respective first PE along y (myidy=0).
    1586                       IF ( ( section(is,s) >= nys  .AND.                       &
    1587                              section(is,s) <= nyn )  .OR.                      &
    1588                            ( section(is,s) == -1  .AND.  myidy == 0 ) )  THEN
     1605                      IF ( ( section(is,s_ind) >= nys  .AND.                   &
     1606                             section(is,s_ind) <= nyn )  .OR.                  &
     1607                           ( section(is,s_ind) == -1  .AND.  myidy == 0 ) )  THEN
    15891608#if defined( __netcdf )
    15901609!
     
    16151634                         DO  i = 0, io_blocks-1
    16161635                            IF ( i == io_group )  THEN
    1617                                IF ( ( section(is,s) >= nys  .AND.              &
    1618                                       section(is,s) <= nyn )  .OR.             &
    1619                                     ( section(is,s) == -1  .AND.               &
     1636                               IF ( ( section(is,s_ind) >= nys  .AND.          &
     1637                                      section(is,s_ind) <= nyn )  .OR.         &
     1638                                    ( section(is,s_ind) == -1  .AND.           &
    16201639                                      nys-1 == -1 ) )                          &
    16211640                               THEN
     
    16431662!
    16441663!--                         Local array can be relocated directly.
    1645                             IF ( ( section(is,s) >= nys  .AND.                 &
    1646                                    section(is,s) <= nyn )  .OR.                &
    1647                                  ( section(is,s) == -1  .AND.  nys-1 == -1 ) ) &
    1648                             THEN
     1664                            IF ( ( section(is,s_ind) >= nys  .AND.              &
     1665                                   section(is,s_ind) <= nyn )  .OR.             &
     1666                                 ( section(is,s_ind) == -1  .AND.              &
     1667                                   nys-1 == -1 ) )  THEN
    16491668                               total_2d(nxlg:nxrg,nzb_do:nzt_do) = local_2d
    16501669                            ENDIF
     
    16911710!--                         If the cross section resides on the PE, send the
    16921711!--                         local index limits, otherwise send -9999 to PE0.
    1693                             IF ( ( section(is,s) >= nys  .AND.                 &
    1694                                    section(is,s) <= nyn )  .OR.                &
    1695                                  ( section(is,s) == -1  .AND.  nys-1 == -1 ) ) &
     1712                            IF ( ( section(is,s_ind) >= nys  .AND.              &
     1713                                   section(is,s_ind) <= nyn )  .OR.             &
     1714                                 ( section(is,s_ind) == -1  .AND.  nys-1 == -1 ) ) &
    16961715                            THEN
    16971716                               ind(1) = nxlg; ind(2) = nxrg
     
    17561775!
    17571776!--                If required, carry out averaging along x
    1758                    IF ( section(is,s) == -1 )  THEN
     1777                   IF ( section(is,s_ind) == -1 )  THEN
    17591778
    17601779                      ALLOCATE( local_2d_l(nysg:nyng,nzb_do:nzt_do) )
     
    17891808!--                   Just store the respective section on the local array
    17901809!--                   (but only if it is available on this PE!)
    1791                       IF ( section(is,s) >= nxl  .AND.  section(is,s) <= nxr ) &
     1810                      IF ( section(is,s_ind) >= nxl  .AND.  section(is,s_ind) <= nxr ) &
    17921811                      THEN
    1793                          local_2d = local_pf(section(is,s),:,nzb_do:nzt_do)
     1812                         local_2d = local_pf(section(is,s_ind),:,nzb_do:nzt_do)
    17941813                      ENDIF
    17951814
     
    18031822!--                   sections reside. Cross sections averaged along x are
    18041823!--                   output on the respective first PE along x (myidx=0).
    1805                       IF ( ( section(is,s) >= nxl  .AND.                       &
    1806                              section(is,s) <= nxr )  .OR.                      &
    1807                            ( section(is,s) == -1  .AND.  myidx == 0 ) )  THEN
     1824                      IF ( ( section(is,s_ind) >= nxl  .AND.                       &
     1825                             section(is,s_ind) <= nxr )  .OR.                      &
     1826                           ( section(is,s_ind) == -1  .AND.  myidx == 0 ) )  THEN
    18081827#if defined( __netcdf )
    18091828!
     
    18341853                         DO  i = 0, io_blocks-1
    18351854                            IF ( i == io_group )  THEN
    1836                                IF ( ( section(is,s) >= nxl  .AND.              &
    1837                                       section(is,s) <= nxr )  .OR.             &
    1838                                     ( section(is,s) == -1  .AND.               &
     1855                               IF ( ( section(is,s_ind) >= nxl  .AND.          &
     1856                                      section(is,s_ind) <= nxr )  .OR.         &
     1857                                    ( section(is,s_ind) == -1  .AND.           &
    18391858                                      nxl-1 == -1 ) )                          &
    18401859                               THEN
     
    18621881!
    18631882!--                         Local array can be relocated directly.
    1864                             IF ( ( section(is,s) >= nxl  .AND.                 &
    1865                                    section(is,s) <= nxr )   .OR.               &
    1866                                  ( section(is,s) == -1  .AND.  nxl-1 == -1 ) ) &
     1883                            IF ( ( section(is,s_ind) >= nxl  .AND.             &
     1884                                   section(is,s_ind) <= nxr )   .OR.           &
     1885                                 ( section(is,s_ind) == -1  .AND.  nxl-1 == -1 ) ) &
    18671886                            THEN
    18681887                               total_2d(nysg:nyng,nzb_do:nzt_do) = local_2d
     
    19101929!--                         If the cross section resides on the PE, send the
    19111930!--                         local index limits, otherwise send -9999 to PE0.
    1912                             IF ( ( section(is,s) >= nxl  .AND.                 &
    1913                                    section(is,s) <= nxr )  .OR.                &
    1914                                  ( section(is,s) == -1  .AND.  nxl-1 == -1 ) ) &
     1931                            IF ( ( section(is,s_ind) >= nxl  .AND.              &
     1932                                   section(is,s_ind) <= nxr )  .OR.             &
     1933                                 ( section(is,s_ind) == -1  .AND.  nxl-1 == -1 ) ) &
    19151934                            THEN
    19161935                               ind(1) = nysg; ind(2) = nyng
     
    21482167!
    21492168!-- Close plot output file.
    2150     file_id = 20 + s
     2169    file_id = 20 + s_ind
    21512170
    21522171    IF ( data_output_2d_on_each_pe )  THEN
Note: See TracChangeset for help on using the changeset viewer.