Ignore:
Timestamp:
Oct 1, 2018 2:37:10 AM (6 years ago)
Author:
raasch
Message:

modularization of the ocean code

File:
1 edited

Legend:

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

    r3289 r3294  
    2525! -----------------
    2626! $Id$
     27! changes concerning modularization of ocean option
     28!
     29! 3289 2018-09-28 10:23:58Z suehring
    2730! Introduce module parameter for number of inflow profiles
    2831!
     
    7780
    7881    USE control_parameters
    79      
    8082
    8183    IMPLICIT NONE
     
    99101
    100102
    101     PUBLIC rrd_global, rrd_read_parts_of_global, rrd_local,      &
    102            rrd_skip_global
     103    PUBLIC rrd_global, rrd_read_parts_of_global, rrd_local, rrd_skip_global
    103104
    104105
    105106 CONTAINS
    106107
     108!------------------------------------------------------------------------------!
    107109! Description:
    108110! ------------
     
    115117       USE arrays_3d,                                                          &
    116118           ONLY:  inflow_damping_factor, mean_inflow_profiles, pt_init,        &
    117                   q_init, ref_state, s_init, sa_init, u_init, ug, v_init, vg
     119                  q_init, ref_state, sa_init, s_init, u_init, ug, v_init, vg
    118120
    119121       USE bulk_cloud_model_mod,                                               &
     
    140142       USE netcdf_interface,                                                   &
    141143           ONLY:  netcdf_precision, output_for_t0
     144
     145       USE ocean_mod,                                                          &
     146           ONLY:  ocean_rrd_global
    142147
    143148       USE particle_attributes,                                                &
     
    177182
    178183       CALL check_open( 13 )
    179 
    180 !
    181 !-- Make version number check first
     184!
     185!--    Make version number check first
    182186       READ ( 13 )  length
    183187       READ ( 13 )  restart_string(1:length)
     
    196200
    197201!
    198 !-- Read number of PEs and horizontal index bounds of all PEs used in previous
    199 !-- run
     202!--    Read number of PEs and horizontal index bounds of all PEs used in the
     203!--    previous run
    200204       READ ( 13 )  length
    201205       READ ( 13 )  restart_string(1:length)
     
    223227
    224228!
    225 !-- Read vertical number of gridpoints and number of different areas used
    226 !-- for computing statistics. Allocate arrays depending on these values,
    227 !-- which are needed for the following read instructions.
     229!--    Read vertical number of gridpoints and number of different areas used
     230!--    for computing statistics. Allocate arrays depending on these values,
     231!--    which are needed for the following read instructions.
    228232       READ ( 13 )  length
    229233       READ ( 13 )  restart_string(1:length)
     
    257261       ENDIF
    258262       READ ( 13 )  statistic_regions
     263
    259264       IF ( .NOT. ALLOCATED( ug ) )  THEN
    260265          ALLOCATE( ug(0:nz+1), u_init(0:nz+1), vg(0:nz+1),                    &
     
    266271
    267272!
    268 !-- Now read all control parameters:
    269 !-- Caution: When the following read instructions have been changed, the
    270 !-- -------  version number stored in the variable binary_version_global has to
    271 !--          be increased. The same changes must also be done in
    272 !--          wrd_write_global.
     273!--    Now read all control parameters:
     274!--    Caution: When the following read instructions have been changed, the
     275!--    -------  version number stored in the variable binary_version_global has
     276!--             to be increased. The same changes must also be done in
     277!--             wrd_write_global.
    273278       READ ( 13 )  length
    274279       READ ( 13 )  restart_string(1:length)
     
    318323             CASE ( 'bc_s_t' )
    319324                READ ( 13 )  bc_s_t
    320              CASE ( 'bc_sa_t' )
    321                 READ ( 13 )  bc_sa_t
    322325             CASE ( 'bc_uv_b' )
    323326                READ ( 13 )  bc_uv_b
    324327             CASE ( 'bc_uv_t' )
    325328                READ ( 13 )  bc_uv_t
    326              CASE ( 'bottom_salinityflux' )
    327                 READ ( 13 )  bottom_salinityflux
    328329             CASE ( 'building_height' )
    329330                READ ( 13 )  building_height
     
    496497                READ ( 13 )  ny
    497498                ny_on_file = ny
    498              CASE ( 'ocean' )
    499                 READ ( 13 )  ocean
     499             CASE ( 'ocean_mode' )
     500                READ ( 13 )  ocean_mode
    500501             CASE ( 'old_dt' )
    501502                READ ( 13 )  old_dt
     
    580581             CASE ( 's_vertical_gradient_level_ind' )
    581582                READ ( 13 )  s_vertical_gradient_level_ind
    582              CASE ( 'sa_init' )
    583                 READ ( 13 )  sa_init
    584              CASE ( 'sa_surface' )
    585                 READ ( 13 )  sa_surface
    586              CASE ( 'sa_vertical_gradient' )
    587                 READ ( 13 )  sa_vertical_gradient
    588              CASE ( 'sa_vertical_gradient_level' )
    589                 READ ( 13 )  sa_vertical_gradient_level
    590583             CASE ( 'scalar_advec' )
    591584                READ ( 13 )  scalar_advec
     
    662655             CASE ( 'top_momentumflux_v' )
    663656                READ ( 13 )  top_momentumflux_v
    664              CASE ( 'top_salinityflux' )
    665                 READ ( 13 )  top_salinityflux
    666657             CASE ( 'top_scalarflux' )
    667658                READ ( 13 )  top_scalarflux
     
    754745             CASE ( 'wall_humidityflux' )
    755746                READ ( 13 )  wall_humidityflux
    756              CASE ( 'wall_salinityflux' )
    757                 READ ( 13 )  wall_salinityflux
    758747             CASE ( 'wall_scalarflux' )
    759748                READ ( 13 )  wall_scalarflux
     
    769758                READ ( 13 )  z_i
    770759
    771 
    772760             CASE DEFAULT
    773 
    774                 IF ( .NOT. found ) CALL bcm_rrd_global( found )
    775 
    776                 IF ( .NOT. found ) CALL wtm_rrd_global( found )
    777 
    778                 IF ( .NOT. found ) CALL flight_rrd_global( found )
    779 
    780                 IF ( .NOT. found ) CALL stg_rrd_global ( found )
    781 
    782                 IF ( .NOT. found ) CALL gust_rrd_global( found )
    783 
    784                 IF ( .NOT. found ) CALL user_rrd_global( found )
     761!
     762!--             Read global variables from of other modules
     763                IF ( .NOT. found )  CALL bcm_rrd_global( found )
     764                IF ( .NOT. found )  CALL flight_rrd_global( found )
     765                IF ( .NOT. found )  CALL gust_rrd_global( found )
     766                IF ( .NOT. found )  CALL ocean_rrd_global( found )
     767                IF ( .NOT. found )  CALL stg_rrd_global ( found )
     768                IF ( .NOT. found )  CALL wtm_rrd_global( found )
     769!
     770!--             Read user-defined global variables
     771                IF ( .NOT. found )  CALL user_rrd_global( found )
    785772
    786773                IF ( .NOT. found )  THEN
     
    10491036
    10501037    USE arrays_3d,                                                             &
    1051         ONLY:  e, kh, km, p, pt, q, ql, &
    1052                s, sa, u, u_m_l, u_m_n, u_m_r, u_m_s, v, v_m_l, v_m_n,      &
    1053                v_m_r, v_m_s, vpt, w, w_m_l, w_m_n, w_m_r, w_m_s
     1038        ONLY:  e, kh, km, p, pt, q, ql, s, u, u_m_l, u_m_n, u_m_r, u_m_s,      &
     1039               v, v_m_l, v_m_n, v_m_r, v_m_s, vpt, w, w_m_l, w_m_n, w_m_r, w_m_s
     1040
     1041    USE bulk_cloud_model_mod,                                                  &
     1042        ONLY :  bcm_rrd_local
    10541043
    10551044    USE averaging
     
    10731062        ONLY:  lsm_rrd_local
    10741063
    1075     USE bulk_cloud_model_mod,                                                  &
    1076         ONLY :  bcm_rrd_local
     1064    USE ocean_mod,                                                             &
     1065        ONLY:  ocean_rrd_local
    10771066
    10781067    USE particle_attributes,                                                   &
     
    15991588                   DEALLOCATE( tmp_2d_id_random, tmp_2d_seq_random )
    16001589
    1601                 CASE ( 'rho_ocean_av' )
    1602                    IF ( .NOT. ALLOCATED( rho_ocean_av ) )  THEN
    1603                       ALLOCATE( rho_ocean_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
    1604                    ENDIF
    1605                    IF ( k == 1 )  READ ( 13 )  tmp_3d
    1606                    rho_ocean_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =   &
    1607                       tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
    1608                            
    16091590                CASE ( 's' )
    16101591                   IF ( k == 1 )  READ ( 13 )  tmp_3d
     
    16181599                   IF ( k == 1 )  READ ( 13 )  tmp_3d
    16191600                   s_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =           &
    1620                       tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
    1621 
    1622                 CASE ( 'sa' )
    1623                    IF ( k == 1 )  READ ( 13 )  tmp_3d
    1624                    sa(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =             &
    1625                       tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
    1626 
    1627                 CASE ( 'sa_av' )
    1628                    IF ( .NOT. ALLOCATED( sa_av ) )  THEN
    1629                       ALLOCATE( sa_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
    1630                    ENDIF
    1631                    IF ( k == 1 )  READ ( 13 )  tmp_3d
    1632                    sa_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =          &
    16331601                      tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
    16341602
     
    18841852
    18851853!
    1886 !--                Read microphysics module restart data
     1854!--                Read restart data of other modules
    18871855                   IF ( .NOT. found ) CALL bcm_rrd_local( i, k, nxlf,          &
    18881856                                           nxlc, nxl_on_file, nxrf, nxrc,      &
     
    18911859                                           nys_on_file, tmp_2d, tmp_3d, found )
    18921860
    1893 !
    1894 !--                Read surface related variables
    1895                    IF ( .NOT. found ) CALL surface_rrd_local( i, k, nxlf,      &
    1896                                            nxlc, nxl_on_file, nxrf, nxrc,      &
     1861                   IF ( .NOT. found ) CALL chem_rrd_local( i, k, nxlf,         &
     1862                                           nxlc, nxl_on_file, nxrf, nxrc,      &
    18971863                                           nxr_on_file, nynf, nync,            &
    18981864                                           nyn_on_file, nysf, nysc,            &
    1899                                            nys_on_file, found )
    1900 
    1901 !
    1902 !--                Read urban surface restart data
    1903                    IF ( .NOT. found ) CALL usm_rrd_local( i, k, nxlf,          &
     1865                                           nys_on_file, tmp_3d, found )
     1866
     1867                   IF ( .NOT. found ) CALL gust_rrd_local( i, k, nxlf,         &
    19041868                                           nxlc, nxl_on_file, nxrf, nxrc,      &
    19051869                                           nxr_on_file, nynf, nync,            &
    19061870                                           nyn_on_file, nysf, nysc,            &
    1907                                            nys_on_file, found )
    1908 
    1909 !
    1910 !--                Read land surface restart data
     1871                                           nys_on_file, tmp_2d, tmp_3d, found )
     1872
    19111873                   IF ( .NOT. found ) CALL lsm_rrd_local( i, k, nxlf,          &
    19121874                                           nxlc, nxl_on_file, nxrf, nxrc,      &
     
    19151877                                           nys_on_file, tmp_2d, found )
    19161878
    1917 !
    1918 !--                Read radiation restart data
     1879                   IF ( .NOT. found ) CALL ocean_rrd_local( i, k, nxlf,        &
     1880                                           nxlc, nxl_on_file, nxrf, nxrc,      &
     1881                                           nxr_on_file, nynf, nync,            &
     1882                                           nyn_on_file, nysf, nysc,            &
     1883                                           nys_on_file, tmp_2d, tmp_3d, found )
     1884
    19191885                   IF ( .NOT. found ) CALL radiation_rrd_local( i, k, nxlf,    &
    19201886                                           nxlc, nxl_on_file, nxrf, nxrc,      &
     
    19231889                                           nys_on_file, tmp_2d, tmp_3d, found )
    19241890
    1925 !
    1926 !--                Read chemistry restart data
    1927                    IF ( .NOT. found ) CALL chem_rrd_local( i, k, nxlf,         &
     1891                   IF ( .NOT. found ) CALL surface_rrd_local( i, k, nxlf,      &
    19281892                                           nxlc, nxl_on_file, nxrf, nxrc,      &
    19291893                                           nxr_on_file, nynf, nync,            &
    19301894                                           nyn_on_file, nysf, nysc,            &
    1931                                            nys_on_file, tmp_3d, found )
    1932 
    1933 !
    1934 !--                Read gust module restart data
    1935                    IF ( .NOT. found ) CALL gust_rrd_local( i, k, nxlf,         &
     1895                                           nys_on_file, found )
     1896
     1897                   IF ( .NOT. found ) CALL usm_rrd_local( i, k, nxlf,          &
    19361898                                           nxlc, nxl_on_file, nxrf, nxrc,      &
    19371899                                           nxr_on_file, nynf, nync,            &
    19381900                                           nyn_on_file, nysf, nysc,            &
    1939                                            nys_on_file, tmp_2d, tmp_3d, found )
     1901                                           nys_on_file, found )
    19401902
    19411903!
Note: See TracChangeset for help on using the changeset viewer.