Ignore:
Timestamp:
Dec 18, 2017 6:33:49 PM (6 years ago)
Author:
suehring
Message:

Bugfixes in radiation and restarts in LSM

File:
1 edited

Legend:

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

    r2705 r2706  
    2020! Current revisions:
    2121! -----------------
    22 !
     22! Bugfix, read surface temperature in case of restart runs.
    2323!
    2424! Former revisions:
     
    17681768                        (0.81_wp * (0.004_wp * surf%rad_sw_in(m)               &
    17691769                         + 1.0_wp)) )
     1770
    17701771!
    17711772!--    f2: correction for soil moisture availability to plants (the
     
    19151916
    19161917       ENDIF
    1917 
    19181918
    19191919       tend = 0.0_wp
     
    40524052             ENDDO
    40534053          ENDDO
    4054 
    4055 !
    4056 !--    Actions for restart runs
    4057        ELSE
    4058 !
    4059 !--       Horizontal surfaces
    4060           DO  m = 1, surf_lsm_h%ns
    4061              i   = surf_lsm_h%i(m)           
    4062              j   = surf_lsm_h%j(m)
    4063              k   = surf_lsm_h%k(m)         
    4064              t_surface_h%var_1d(m) = pt(k-1,j,i) * exn
    4065           ENDDO
    4066 !
    4067 !--       Vertical surfaces
    4068           DO  l = 0, 3
    4069 !
    4070 !--          Set index offset of surface element, seen from atmospheric grid point
    4071              j_off = surf_lsm_v(l)%joff
    4072              i_off = surf_lsm_v(l)%ioff
    4073 
    4074              DO  m = 1, surf_lsm_v(l)%ns
    4075                 i   = surf_lsm_v(l)%i(m)           
    4076                 j   = surf_lsm_v(l)%j(m)
    4077                 k   = surf_lsm_v(l)%k(m)         
    4078                 t_surface_v(l)%var_1d(m) = pt(k,j+j_off,i+i_off) * exn
    4079              ENDDO
    4080           ENDDO
    4081 
    40824054       ENDIF
    40834055!
     
    42454217       t_soil_h_p    = t_soil_h
    42464218       m_soil_h_p    = m_soil_h
    4247        m_liq_h_p  = m_liq_h
     4219       m_liq_h_p     = m_liq_h
    42484220       t_surface_h_p = t_surface_h
    42494221
    42504222       t_soil_v_p    = t_soil_v
    42514223       m_soil_v_p    = m_soil_v
    4252        m_liq_v_p  = m_liq_v
     4224       m_liq_v_p     = m_liq_v
    42534225       t_surface_v_p = t_surface_v
    42544226
     
    58245796       ENDDO
    58255797
    5826 
    58275798       WRITE ( 14 ) 'lsm_start_index_h   '
    58285799       WRITE ( 14 ) surf_lsm_h%start_index
     
    58415812          WRITE ( 14 ) m_liq_v(l)%var_1d         
    58425813       ENDDO
     5814
     5815       WRITE ( 14 ) 'lsm_start_index_h   '
     5816       WRITE ( 14 ) surf_lsm_h%start_index
     5817       WRITE ( 14 ) 'lsm_end_index_h     '
     5818       WRITE ( 14 ) surf_lsm_h%end_index
     5819       WRITE ( 14 ) 't_surface_h         '
     5820       WRITE ( 14 ) t_surface_h%var_1d
     5821       
     5822       DO  l = 0, 3
     5823          WRITE ( 14 ) 'lsm_start_index_v   '
     5824          WRITE ( 14 ) surf_lsm_v(l)%start_index
     5825          WRITE ( 14 ) 'lsm_end_index_v     '
     5826          WRITE ( 14 ) surf_lsm_v(l)%end_index
     5827          WRITE( dum, '(I1)')  l         
     5828          WRITE ( 14 ) 't_surface_v(' // dum // ')      '
     5829          WRITE ( 14 ) t_surface_v(l)%var_1d         
     5830       ENDDO
     5831
    58435832
    58445833       WRITE ( 14 )  '*** end lsm ***     '
     
    63406329
    63416330
     6331                CASE ( 't_surface_h' )
     6332                 
     6333                   IF ( k == 1 )  THEN
     6334                      IF ( .NOT.  ALLOCATED( t_surface_h%var_1d ) )            &
     6335                         ALLOCATE( t_surface_h%var_1d(1:surf_lsm_h%ns) )
     6336                      READ ( 13 )  tmp_walltype_h_1d%var_1d
     6337                   ENDIF
     6338                   CALL surface_restore_elements(                              &
     6339                                              t_surface_h%var_1d,              &
     6340                                              tmp_walltype_h_1d%var_1d,        &
     6341                                              surf_lsm_h%start_index,          &
     6342                                              start_index_on_file,             &
     6343                                              end_index_on_file,               &
     6344                                              nxlc, nysc,                      &
     6345                                              nxlf, nxrf, nysf, nynf,          &
     6346                                              nys_on_file, nyn_on_file,        &
     6347                                              nxl_on_file,nxr_on_file )
     6348
     6349                CASE ( 't_surface_v(0)' )
     6350                 
     6351                   IF ( k == 1 )  THEN
     6352                      IF ( .NOT.  ALLOCATED( t_surface_v(0)%var_1d ) )         &
     6353                         ALLOCATE( t_surface_v(0)%var_1d(1:surf_lsm_v(0)%ns) )
     6354                      READ ( 13 )  tmp_walltype_v_1d(0)%var_1d
     6355                   ENDIF
     6356                   CALL surface_restore_elements(                              &
     6357                                           t_surface_v(0)%var_1d,              &
     6358                                           tmp_walltype_v_1d(0)%var_1d,        &
     6359                                           surf_lsm_v(0)%start_index,          &
     6360                                           start_index_on_file,                &
     6361                                           end_index_on_file,                  &
     6362                                           nxlc, nysc,                         &
     6363                                           nxlf, nxrf, nysf, nynf,             &
     6364                                           nys_on_file, nyn_on_file,           &
     6365                                           nxl_on_file,nxr_on_file )
     6366
     6367                CASE ( 't_surface_v(1)' )
     6368                 
     6369                   IF ( k == 1 )  THEN
     6370                      IF ( .NOT.  ALLOCATED( t_surface_v(1)%var_1d ) )         &
     6371                         ALLOCATE( t_surface_v(1)%var_1d(1:surf_lsm_v(1)%ns) )
     6372                      READ ( 13 )  tmp_walltype_v_1d(1)%var_1d
     6373                   ENDIF
     6374                   CALL surface_restore_elements(                              &
     6375                                           t_surface_v(1)%var_1d,              &
     6376                                           tmp_walltype_v_1d(1)%var_1d,        &
     6377                                           surf_lsm_v(1)%start_index,          &
     6378                                           start_index_on_file,                &
     6379                                           end_index_on_file,                  &
     6380                                           nxlc, nysc,                         &
     6381                                           nxlf, nxrf, nysf, nynf,             &
     6382                                           nys_on_file, nyn_on_file,           &
     6383                                           nxl_on_file,nxr_on_file )
     6384
     6385                CASE ( 't_surface_v(2)' )
     6386                 
     6387                   IF ( k == 1 )  THEN
     6388                      IF ( .NOT.  ALLOCATED( t_surface_v(2)%var_1d ) )         &
     6389                         ALLOCATE( t_surface_v(2)%var_1d(1:surf_lsm_v(2)%ns) )
     6390                      READ ( 13 )  tmp_walltype_v_1d(2)%var_1d
     6391                   ENDIF
     6392                   CALL surface_restore_elements(                              &
     6393                                           t_surface_v(2)%var_1d,              &
     6394                                           tmp_walltype_v_1d(2)%var_1d,        &
     6395                                           surf_lsm_v(2)%start_index,          &
     6396                                           start_index_on_file,                &
     6397                                           end_index_on_file,                  &
     6398                                           nxlc, nysc,                         &
     6399                                           nxlf, nxrf, nysf, nynf,             &
     6400                                           nys_on_file, nyn_on_file,           &
     6401                                           nxl_on_file,nxr_on_file )
     6402
     6403                CASE ( 't_surface_v(3)' )
     6404                 
     6405                   IF ( k == 1 )  THEN
     6406                      IF ( .NOT.  ALLOCATED( t_surface_v(3)%var_1d ) )         &
     6407                         ALLOCATE( t_surface_v(3)%var_1d(1:surf_lsm_v(3)%ns) )
     6408                      READ ( 13 )  tmp_walltype_v_1d(3)%var_1d
     6409                   ENDIF
     6410                   CALL surface_restore_elements(                              &
     6411                                           t_surface_v(3)%var_1d,              &
     6412                                           tmp_walltype_v_1d(3)%var_1d,        &
     6413                                           surf_lsm_v(3)%start_index,          &
     6414                                           start_index_on_file,                &
     6415                                           end_index_on_file,                  &
     6416                                           nxlc, nysc,                         &
     6417                                           nxlf, nxrf, nysf, nynf,             &
     6418                                           nys_on_file, nyn_on_file,           &
     6419                                           nxl_on_file,nxr_on_file )
     6420
    63426421               CASE DEFAULT
    63436422                  WRITE( message_string, * ) 'unknown variable named "',       &
Note: See TracChangeset for help on using the changeset viewer.