Ignore:
Timestamp:
Mar 3, 2015 2:18:16 PM (9 years ago)
Author:
maronga
Message:

land surface model released

File:
1 edited

Legend:

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

    r1354 r1551  
    2323! Current revisions:
    2424! ------------------
    25 !
     25! Added support for land surface model and radiation model output. In the course
     26! of this action a new vertical grid zs (soil) was introduced.
    2627!
    2728! Former revisions:
     
    9798! In case of extend = .TRUE.:
    9899! Find out if dimensions and variables of an existing file match the values
    99 ! of the actual run. If so, get all necessary informations (ids, etc.) from
     100! of the actual run. If so, get all necessary information (ids, etc.) from
    100101! this file.
    101102!
     
    130131
    131132    USE kinds
     133
     134    USE land_surface_model_mod,                                                &
     135        ONLY: land_surface, nzb_soil, nzt_soil, id_dim_zs_xy, id_dim_zs_xz,    &
     136              id_dim_zs_yz, id_dim_zs_3d, id_dim_zs_mask, id_var_zs_xy,        &
     137              id_var_zs_xz, id_var_zs_yz ,id_var_zs_3d, id_var_zs_mask,        &
     138              nzs, zs
    132139
    133140    USE pegrid
     
    181188    INTEGER(iwp) ::  kk                                      !:
    182189    INTEGER(iwp) ::  ns                                      !:
     190    INTEGER(iwp) ::  ns_do                                   !: actual value of ns for soil model data
    183191    INTEGER(iwp) ::  ns_old                                  !:
    184192    INTEGER(iwp) ::  ntime_count                             !:
     
    439447!
    440448!--       In case of non-flat topography define 2d-arrays containing the height
    441 !--       informations
     449!--       information
    442450          IF ( TRIM( topography ) /= 'flat' )  THEN
    443451!
     
    478486
    479487          ENDIF             
    480 
     488 
     489          IF ( land_surface )  THEN
     490!
     491!--          Define vertical coordinate grid (zw grid)
     492             nc_stat = NF90_DEF_DIM( id_set_mask(mid,av), 'zs_3d', &
     493                                     mask_size(mid,3), id_dim_zs_mask(mid,av) )
     494             CALL handle_netcdf_error( 'netcdf', 536 )
     495
     496             nc_stat = NF90_DEF_VAR( id_set_mask(mid,av), 'zs_3d', NF90_DOUBLE, &
     497                                     id_dim_zs_mask(mid,av), &
     498                                     id_var_zs_mask(mid,av) )
     499             CALL handle_netcdf_error( 'netcdf', 536 )
     500
     501             nc_stat = NF90_PUT_ATT( id_set_mask(mid,av), id_var_zs_mask(mid,av), &
     502                                  'units', 'meters' )
     503             CALL handle_netcdf_error( 'netcdf', 537 )
     504
     505          ENDIF
    481506
    482507!
     
    521546                   grid_y = 'y'
    522547                   grid_z = 'zw'
     548!
     549!--             soil grid
     550                CASE ( 't_soil', 'm_soil' )
     551
     552                   grid_x = 'x'
     553                   grid_y = 'y'
     554                   grid_z = 'zs'
    523555
    524556                CASE DEFAULT
     
    548580             ELSEIF ( grid_z == 'zw' )  THEN
    549581                id_z = id_dim_zw_mask(mid,av)
     582             ELSEIF ( grid_z == "zs" )  THEN
     583                id_z = id_dim_zs_mask(mid,av)
    550584             ENDIF
    551585
     
    692726
    693727          ENDIF
     728
     729          IF ( land_surface )  THEN
     730!
     731!--          Write zs data (vertical axes for soil model), use negative values
     732!--          to indicate soil depth
     733             ALLOCATE( netcdf_data(mask_size(mid,3)) )
     734
     735             netcdf_data = zs( mask_k_global(mid,:mask_size(mid,3)) )
     736
     737             nc_stat = NF90_PUT_VAR( id_set_mask(mid,av), id_var_zs_mask(mid,av), &
     738                                     netcdf_data, start = (/ 1 /), &
     739                                     count = (/ mask_size(mid,3) /) )
     740             CALL handle_netcdf_error( 'netcdf', 538 )
     741
     742             DEALLOCATE( netcdf_data )
     743
     744          ENDIF
     745
    694746!
    695747!--       restore original parameter file_id (=formal parameter av) into av
     
    9821034!
    9831035!--       In case of non-flat topography define 2d-arrays containing the height
    984 !--       informations
     1036!--       information
    9851037          IF ( TRIM( topography ) /= 'flat' )  THEN
    9861038!
     
    10161068          ENDIF             
    10171069
     1070          IF ( land_surface )  THEN
     1071!
     1072!--          Define vertical coordinate grid (zs grid)
     1073             nc_stat = NF90_DEF_DIM( id_set_3d(av), 'zs_3d', nzt_soil-nzb_soil+1, &
     1074                                     id_dim_zs_3d(av) )
     1075             CALL handle_netcdf_error( 'netcdf', 70 )
     1076
     1077             nc_stat = NF90_DEF_VAR( id_set_3d(av), 'zs_3d', NF90_DOUBLE, &
     1078                                     id_dim_zs_3d(av), id_var_zs_3d(av) )
     1079             CALL handle_netcdf_error( 'netcdf', 71 )
     1080
     1081             nc_stat = NF90_PUT_ATT( id_set_3d(av), id_var_zs_3d(av), 'units', &
     1082                                     'meters' )
     1083             CALL handle_netcdf_error( 'netcdf', 72 )
     1084
     1085          ENDIF
    10181086
    10191087!
     
    10581126                   grid_y = 'y'
    10591127                   grid_z = 'zw'
     1128!
     1129!--             soil grid
     1130                CASE ( 't_soil', 'm_soil' )
     1131
     1132                   grid_x = 'x'
     1133                   grid_y = 'y'
     1134                   grid_z = 'zs'
    10601135
    10611136                CASE DEFAULT
     
    10851160             ELSEIF ( grid_z == 'zw' )  THEN
    10861161                id_z = id_dim_zw_3d(av)
     1162             ELSEIF ( grid_z == 'zs' )  THEN
     1163                id_z = id_dim_zs_3d(av)
    10871164             ENDIF
    10881165
     
    12391316
    12401317             ENDIF
     1318
     1319             IF ( land_surface )  THEN
     1320!
     1321!--             Write zs grid
     1322                nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_zs_3d(av),  &
     1323                                        - zs(nzb_soil:nzt_soil), start = (/ 1 /), &
     1324                                        count = (/ nzt_soil-nzb_soil+1 /) )
     1325                CALL handle_netcdf_error( 'netcdf', 86 )
     1326             ENDIF
     1327
    12411328          ENDIF
    12421329
     
    14961583          CALL handle_netcdf_error( 'netcdf', 107 )
    14971584
     1585
     1586          IF ( land_surface )  THEN
     1587
     1588             ns_do = 0
     1589             DO WHILE ( section(ns_do+1,1) < nzs )
     1590                ns_do = ns_do + 1
     1591             ENDDO
     1592!
     1593!--          Define vertical coordinate grid (zs grid)
     1594             nc_stat = NF90_DEF_DIM( id_set_xy(av), 'zs_xy', ns_do, id_dim_zs_xy(av) )
     1595             CALL handle_netcdf_error( 'netcdf', 539 )
     1596
     1597             nc_stat = NF90_DEF_VAR( id_set_xy(av), 'zs_xy', NF90_DOUBLE, &
     1598                                     id_dim_zs_xy(av), id_var_zs_xy(av) )
     1599             CALL handle_netcdf_error( 'netcdf', 540 )
     1600
     1601             nc_stat = NF90_PUT_ATT( id_set_xy(av), id_var_zs_xy(av), 'units', &
     1602                                  'meters' )
     1603             CALL handle_netcdf_error( 'netcdf', 541 )
     1604
     1605          ENDIF
     1606
    14981607!
    14991608!--       Define a pseudo vertical coordinate grid for the surface variables
     
    15771686!
    15781687!--       In case of non-flat topography define 2d-arrays containing the height
    1579 !--       informations
     1688!--       information
    15801689          IF ( TRIM( topography ) /= 'flat' )  THEN
    15811690!
     
    16111720          ENDIF
    16121721
    1613 
    16141722!
    16151723!--       Define the variables
     
    16711779                         grid_y = 'y'
    16721780                         grid_z = 'zw'
     1781!
     1782!--                   soil grid
     1783                      CASE ( 't_soil_xy', 'm_soil_xy' )
     1784                         grid_x = 'x'
     1785                         grid_y = 'y'
     1786                         grid_z = 'zs'
    16731787
    16741788                      CASE DEFAULT
     
    16981812                   ELSEIF ( grid_z == 'zw' )  THEN
    16991813                      id_z = id_dim_zw_xy(av)
     1814                   ELSEIF ( grid_z == 'zs' )  THEN
     1815                      id_z = id_dim_zs_xy(av)
    17001816                   ENDIF
    17011817
     
    18131929
    18141930!
     1931!--             Write zs data
     1932             IF ( land_surface )  THEN
     1933                ns_do = 0
     1934                DO  i = 1, ns
     1935                   IF( section(i,1) == -1 )  THEN
     1936                      netcdf_data(i) = 1.0_wp  ! section averaged along z
     1937                      ns_do = ns_do + 1
     1938                   ELSEIF ( section(i,1) < nzs )  THEN
     1939                      netcdf_data(i) = - zs( section(i,1) )
     1940                      ns_do = ns_do + 1
     1941                   ENDIF
     1942                ENDDO
     1943
     1944                nc_stat = NF90_PUT_VAR( id_set_xy(av), id_var_zs_xy(av), &
     1945                                        netcdf_data(1:ns_do), start = (/ 1 /),    &
     1946                                        count = (/ ns_do /) )
     1947                CALL handle_netcdf_error( 'netcdf', 124 )
     1948
     1949             ENDIF
     1950
     1951!
    18151952!--          Write gridpoint number data
    18161953             netcdf_data(1:ns) = section(1:ns,1)
     
    18942031
    18952032             ENDIF
     2033
     2034
     2035
    18962036          ENDIF
    18972037
     
    22402380
    22412381!
    2242 !--       Define the two z-axes (zu and zw)
     2382!--       Define the three z-axes (zu, zw, and zs)
    22432383          nc_stat = NF90_DEF_DIM( id_set_xz(av), 'zu', nz+2, id_dim_zu_xz(av) )
    22442384          CALL handle_netcdf_error( 'netcdf', 153 )
     
    22632403          CALL handle_netcdf_error( 'netcdf', 158 )
    22642404
     2405          IF ( land_surface )  THEN
     2406
     2407             nc_stat = NF90_DEF_DIM( id_set_xz(av), 'zs', nzs, id_dim_zs_xz(av) )
     2408             CALL handle_netcdf_error( 'netcdf', 542 )
     2409
     2410             nc_stat = NF90_DEF_VAR( id_set_xz(av), 'zs', NF90_DOUBLE, &
     2411                                     id_dim_zs_xz(av), id_var_zs_xz(av) )
     2412             CALL handle_netcdf_error( 'netcdf', 543 )
     2413
     2414             nc_stat = NF90_PUT_ATT( id_set_xz(av), id_var_zs_xz(av), 'units', &
     2415                                     'meters' )
     2416             CALL handle_netcdf_error( 'netcdf', 544 )
     2417
     2418          ENDIF
    22652419
    22662420!
     
    23082462                      grid_y = 'y'
    23092463                      grid_z = 'zw'
     2464
     2465!
     2466!--                soil grid
     2467                   CASE ( 't_soil_xz', 'm_soil_xz' )
     2468
     2469                      grid_x = 'x'
     2470                      grid_y = 'y'
     2471                      grid_z = 'zs'
    23102472
    23112473                   CASE DEFAULT
     
    23352497                ELSEIF ( grid_z == 'zw' )  THEN
    23362498                   id_z = id_dim_zw_xz(av)
     2499                ELSEIF ( grid_z == 'zs' )  THEN
     2500                   id_z = id_dim_zs_xz(av)
    23372501                ENDIF
    23382502
     
    25142678                                     count = (/ nz+2 /) )
    25152679             CALL handle_netcdf_error( 'netcdf', 167 )
     2680
     2681!
     2682!--          Write zs data
     2683             IF ( land_surface )  THEN
     2684                netcdf_data(0:nzs-1) = - zs(nzb_soil:nzt_soil)
     2685                nc_stat = NF90_PUT_VAR( id_set_xz(av), id_var_zs_xz(av), &
     2686                                        netcdf_data(0:nzs), start = (/ 1 /),    &
     2687                                        count = (/ nzt_soil-nzb_soil+1 /) )
     2688               CALL handle_netcdf_error( 'netcdf', 548 )
     2689             ENDIF
     2690
    25162691
    25172692             DEALLOCATE( netcdf_data )
     
    29033078          CALL handle_netcdf_error( 'netcdf', 197 )
    29043079
     3080          IF ( land_surface )  THEN
     3081
     3082             nc_stat = NF90_DEF_DIM( id_set_yz(av), 'zs', nzs, id_dim_zs_yz(av) )
     3083             CALL handle_netcdf_error( 'netcdf', 545 )
     3084
     3085             nc_stat = NF90_DEF_VAR( id_set_yz(av), 'zs', NF90_DOUBLE, &
     3086                                     id_dim_zs_yz(av), id_var_zs_yz(av) )
     3087             CALL handle_netcdf_error( 'netcdf', 546 )
     3088
     3089             nc_stat = NF90_PUT_ATT( id_set_yz(av), id_var_zs_yz(av), 'units', &
     3090                                     'meters' )
     3091             CALL handle_netcdf_error( 'netcdf', 547 )
     3092
     3093          ENDIF
     3094
    29053095
    29063096!
     
    29483138                      grid_y = 'y'
    29493139                      grid_z = 'zw'
     3140!
     3141!--                soil grid
     3142                   CASE ( 't_soil_yz', 'm_soil_yz' )
     3143
     3144                      grid_x = 'x'
     3145                      grid_y = 'y'
     3146                      grid_z = 'zs'
    29503147
    29513148                   CASE DEFAULT
     
    29753172                ELSEIF ( grid_z == 'zw' )  THEN
    29763173                   id_z = id_dim_zw_yz(av)
     3174                ELSEIF ( grid_z == 'zs' )  THEN
     3175                   id_z = id_dim_zs_yz(av)
    29773176                ENDIF
    29783177
Note: See TracChangeset for help on using the changeset viewer.