Ignore:
Timestamp:
Nov 25, 2008 7:12:43 AM (15 years ago)
Author:
raasch
Message:

reading mechanism for restart files completely revised

File:
1 edited

Legend:

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

    r198 r216  
    77! Current revisions:
    88! ------------------
    9 !
     9! Origin of the xy-coordinate system shifted from the center of the first
     10! grid cell (indices i=0, j=0) to the south-left corner of this cell.
    1011!
    1112! Former revisions:
     
    457458
    458459!
    459 !--       Write data for x and xu axis (shifted by -dx/2)
     460!--       Write data for x (shifted by +dx/2) and xu axis
    460461          ALLOCATE( netcdf_data(0:nx+1) )
    461462
    462463          DO  i = 0, nx+1
    463              netcdf_data(i) = i * dx
     464             netcdf_data(i) = ( i + 0.5 ) * dx
    464465          ENDDO
    465466
     
    469470
    470471          DO  i = 0, nx+1
    471              netcdf_data(i) = ( i - 0.5 ) * dx
     472             netcdf_data(i) = i * dx
    472473          ENDDO
    473474
     
    480481
    481482!
    482 !--       Write data for y and yv axis (shifted by -dy/2)
     483!--       Write data for y (shifted by +dy/2) and yv axis
    483484          ALLOCATE( netcdf_data(0:ny+1) )
    484485
    485486          DO  i = 0, ny+1
    486              netcdf_data(i) = i * dy
     487             netcdf_data(i) = ( i + 0.5 ) * dy
    487488          ENDDO
    488489
     
    492493
    493494          DO  i = 0, ny+1
    494              netcdf_data(i) = ( i - 0.5 ) * dy
     495             netcdf_data(i) = i * dy
    495496          ENDDO
    496497
     
    10341035
    10351036!
    1036 !--       Write data for x and xu axis (shifted by -dx/2)
     1037!--       Write data for x (shifted by +dx/2) and xu axis
    10371038          ALLOCATE( netcdf_data(0:nx+1) )
    10381039
    10391040          DO  i = 0, nx+1
    1040              netcdf_data(i) = i * dx
     1041             netcdf_data(i) = ( i + 0.5 ) * dx
    10411042          ENDDO
    10421043
     
    10461047
    10471048          DO  i = 0, nx+1
    1048              netcdf_data(i) = ( i - 0.5 ) * dx
     1049             netcdf_data(i) = i * dx
    10491050          ENDDO
    10501051
     
    10571058
    10581059!
    1059 !--       Write data for y and yv axis (shifted by -dy/2)
     1060!--       Write data for y (shifted by +dy/2) and yv axis
    10601061          ALLOCATE( netcdf_data(0:ny+1) )
    10611062
    10621063          DO  i = 0, ny+1
    1063              netcdf_data(i) = i * dy
     1064             netcdf_data(i) = ( i + 0.5 ) * dy
    10641065          ENDDO
    10651066
     
    10691070
    10701071          DO  i = 0, ny+1
    1071              netcdf_data(i) = ( i - 0.5 ) * dy
     1072             netcdf_data(i) = i * dy
    10721073          ENDDO
    10731074
     
    15311532
    15321533!
    1533 !--       Write y_xz data
     1534!--       Write y_xz data (shifted by +dy/2)
     1535          DO  i = 1, ns
     1536             IF( section(i,2) == -1 )  THEN
     1537                netcdf_data(i) = -1.0  ! section averaged along y
     1538             ELSE
     1539                netcdf_data(i) = ( section(i,2) + 0.5 ) * dy
     1540             ENDIF
     1541          ENDDO
     1542          nc_stat = NF90_PUT_VAR( id_set_xz(av), id_var_y_xz(av), netcdf_data, &
     1543                                  start = (/ 1 /), count = (/ ns /) )
     1544          IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 163 )
     1545
     1546!
     1547!--       Write yv_xz data
    15341548          DO  i = 1, ns
    15351549             IF( section(i,2) == -1 )  THEN
     
    15391553             ENDIF
    15401554          ENDDO
    1541           nc_stat = NF90_PUT_VAR( id_set_xz(av), id_var_y_xz(av), netcdf_data, &
    1542                                   start = (/ 1 /), count = (/ ns /) )
    1543           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 163 )
    1544 
    1545 !
    1546 !--       Write yv_xz data
    1547           DO  i = 1, ns
    1548              IF( section(i,2) == -1 )  THEN
    1549                 netcdf_data(i) = -1.0  ! section averaged along y
    1550              ELSE
    1551                 netcdf_data(i) = ( section(i,2) - 0.5 ) * dy
    1552              ENDIF
    1553           ENDDO
    15541555          nc_stat = NF90_PUT_VAR( id_set_xz(av), id_var_yv_xz(av), &
    15551556                                  netcdf_data, start = (/ 1 /),    &
     
    15681569
    15691570!
    1570 !--       Write data for x and xu axis (shifted by -dx/2)
     1571!--       Write data for x (shifted by +dx/2) and xu axis
    15711572          ALLOCATE( netcdf_data(0:nx+1) )
    15721573
    15731574          DO  i = 0, nx+1
    1574              netcdf_data(i) = i * dx
     1575             netcdf_data(i) = ( i + 0.5 ) * dx
    15751576          ENDDO
    15761577
     
    15801581
    15811582          DO  i = 0, nx+1
    1582              netcdf_data(i) = ( i - 0.5 ) * dx
     1583             netcdf_data(i) = i * dx
    15831584          ENDDO
    15841585
     
    20422043
    20432044!
    2044 !--       Write x_yz data
     2045!--       Write x_yz data (shifted by +dx/2)
     2046          DO  i = 1, ns
     2047             IF( section(i,3) == -1 )  THEN
     2048                netcdf_data(i) = -1.0  ! section averaged along x
     2049             ELSE
     2050                netcdf_data(i) = ( section(i,3) + 0.5 ) * dx
     2051             ENDIF
     2052          ENDDO
     2053          nc_stat = NF90_PUT_VAR( id_set_yz(av), id_var_x_yz(av), netcdf_data, &
     2054                                  start = (/ 1 /), count = (/ ns /) )
     2055          IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 202 )
     2056
     2057!
     2058!--       Write x_yz data (xu grid)
    20452059          DO  i = 1, ns
    20462060             IF( section(i,3) == -1 )  THEN
     
    20502064             ENDIF
    20512065          ENDDO
    2052           nc_stat = NF90_PUT_VAR( id_set_yz(av), id_var_x_yz(av), netcdf_data, &
    2053                                   start = (/ 1 /), count = (/ ns /) )
    2054           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 202 )
    2055 
    2056 !
    2057 !--       Write x_yz data (xu grid)
    2058           DO  i = 1, ns
    2059              IF( section(i,3) == -1 )  THEN
    2060                 netcdf_data(i) = -1.0  ! section averaged along x
    2061              ELSE
    2062                 netcdf_data(i) = (section(i,3)-0.5) * dx
    2063              ENDIF
    2064           ENDDO
    20652066          nc_stat = NF90_PUT_VAR( id_set_yz(av), id_var_xu_yz(av), netcdf_data, &
    20662067                                  start = (/ 1 /), count = (/ ns /) )
     
    20782079
    20792080!
    2080 !--       Write data for y and yv axis (shifted by -dy/2)
     2081!--       Write data for y (shifted by +dy/2) and yv axis
    20812082          ALLOCATE( netcdf_data(0:ny+1) )
    20822083
    20832084          DO  j = 0, ny+1
    2084              netcdf_data(j) = j * dy
     2085             netcdf_data(j) = ( j + 0.5 ) * dy
    20852086          ENDDO
    20862087
     
    20902091
    20912092          DO  j = 0, ny+1
    2092              netcdf_data(j) = ( j - 0.5 ) * dy
     2093             netcdf_data(j) = j * dy
    20932094          ENDDO
    20942095
Note: See TracChangeset for help on using the changeset viewer.