Ignore:
Timestamp:
Aug 7, 2017 12:15:38 PM (7 years ago)
Author:
gronemeier
Message:

modularized 1d model

File:
1 moved

Legend:

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

    r2337 r2338  
    1 !> @file init_1d_model.f90
     1!> @file model_1d_mod.f90
    22!------------------------------------------------------------------------------!
    33! This file is part of PALM.
     
    2525! -----------------
    2626! $Id$
     27! renamed init_1d_model to model_1d_mod and and formatted it as a module;
     28! reformatted output of profiles
     29!
     30!
    2731! revised calculation of mixing length
    2832! removed rounding of time step
     
    113117!> @bug 1D model crashes when using small grid spacings in the order of 1 m
    114118!------------------------------------------------------------------------------!
     119 MODULE model_1d_mod
     120
     121    USE arrays_3d,                                                             &
     122        ONLY:  dd2zu, ddzu, ddzw, dzu, l_grid, pt_init, q_init, ug, u_init,    &
     123               vg, v_init, zu
     124   
     125    USE control_parameters,                                                    &
     126        ONLY:  constant_diffusion, constant_flux_layer, dissipation_1d, f, g,  &
     127               humidity, ibc_e_b, intermediate_timestep_count,                 &
     128               intermediate_timestep_count_max, kappa, km_constant,            &
     129               message_string, mixing_length_1d, prandtl_number,               &
     130               roughness_length, run_description_header, simulated_time_chr, timestep_scheme, tsc, z0h_factor
     131
     132    USE indices,                                                               &
     133        ONLY:  nzb, nzb_diff, nzt
     134   
     135    USE kinds
     136
     137    USE pegrid
     138       
     139
     140    IMPLICIT NONE
     141
     142
     143    INTEGER(iwp) ::  current_timestep_number_1d = 0  !< current timestep number (1d-model)
     144    INTEGER(iwp) ::  damp_level_ind_1d               !< lower grid index of damping layer (1d-model) !#
     145
     146    LOGICAL ::  run_control_header_1d = .FALSE.  !< flag for output of run control header (1d-model)
     147    LOGICAL ::  stop_dt_1d = .FALSE.             !< termination flag, used in case of too small timestep (1d-model)
     148
     149    REAL(wp) ::  c_m = 0.4_wp                  !< model constant, 0.4 according to Detering and Etling (1985)
     150    REAL(wp) ::  damp_level_1d = -1.0_wp       !< namelist parameter    !#
     151    REAL(wp) ::  dt_1d = 60.0_wp               !< dynamic timestep (1d-model)
     152    REAL(wp) ::  dt_max_1d = 300.0_wp          !< timestep limit (1d-model)
     153    REAL(wp) ::  dt_pr_1d = 9999999.9_wp       !< namelist parameter     !#
     154    REAL(wp) ::  dt_run_control_1d = 60.0_wp   !< namelist parameter     !#
     155    REAL(wp) ::  end_time_1d = 864000.0_wp     !< namelist parameter     !#
     156    REAL(wp) ::  qs1d                          !< characteristic humidity scale (1d-model)
     157    REAL(wp) ::  simulated_time_1d = 0.0_wp    !< updated simulated time (1d-model)
     158    REAL(wp) ::  time_pr_1d = 0.0_wp           !< updated simulated time for profile output (1d-model)
     159    REAL(wp) ::  time_run_control_1d = 0.0_wp  !< updated simulated time for run-control output (1d-model)
     160    REAL(wp) ::  ts1d                          !< characteristic temperature scale (1d-model)
     161    REAL(wp) ::  us1d                          !< friction velocity (1d-model)                 !#
     162    REAL(wp) ::  usws1d                        !< u-component of the momentum flux (1d-model)  !#
     163    REAL(wp) ::  vsws1d                        !< v-component of the momentum flux (1d-model)  !#
     164    REAL(wp) ::  z01d                          !< roughness length for momentum (1d-model)
     165    REAL(wp) ::  z0h1d                         !< roughness length for scalars (1d-model)
     166
     167
     168    REAL(wp), DIMENSION(:), ALLOCATABLE ::  e1d      !< tke (1d-model)                         !#
     169    REAL(wp), DIMENSION(:), ALLOCATABLE ::  e1d_p    !< prognostic value of tke (1d-model)
     170    REAL(wp), DIMENSION(:), ALLOCATABLE ::  kh1d     !< turbulent diffusion coefficient for heat (1d-model)    !#
     171    REAL(wp), DIMENSION(:), ALLOCATABLE ::  km1d     !< turbulent diffusion coefficient for momentum (1d-model)!#
     172    REAL(wp), DIMENSION(:), ALLOCATABLE ::  l_black  !< mixing length Blackadar (1d-model)
     173    REAL(wp), DIMENSION(:), ALLOCATABLE ::  l1d      !< mixing length for turbulent diffusion coefficients (1d-model) !#
     174    REAL(wp), DIMENSION(:), ALLOCATABLE ::  l1d_diss !< mixing length for dissipation (1d-model)
     175    REAL(wp), DIMENSION(:), ALLOCATABLE ::  rif1d    !< Richardson flux number (1d-model)      !#
     176    REAL(wp), DIMENSION(:), ALLOCATABLE ::  te_e     !< tendency of e (1d-model)
     177    REAL(wp), DIMENSION(:), ALLOCATABLE ::  te_em    !< weighted tendency of e for previous sub-timestep (1d-model)
     178    REAL(wp), DIMENSION(:), ALLOCATABLE ::  te_u     !< tendency of u (1d-model)
     179    REAL(wp), DIMENSION(:), ALLOCATABLE ::  te_um    !< weighted tendency of u for previous sub-timestep (1d-model)
     180    REAL(wp), DIMENSION(:), ALLOCATABLE ::  te_v     !< tendency of v (1d-model)
     181    REAL(wp), DIMENSION(:), ALLOCATABLE ::  te_vm    !< weighted tendency of v for previous sub-timestep (1d-model)
     182    REAL(wp), DIMENSION(:), ALLOCATABLE ::  u1d      !< u-velocity component (1d-model)        !#
     183    REAL(wp), DIMENSION(:), ALLOCATABLE ::  u1d_p    !< prognostic value of u-velocity component (1d-model)
     184    REAL(wp), DIMENSION(:), ALLOCATABLE ::  v1d      !< v-velocity component (1d-model)        !#
     185    REAL(wp), DIMENSION(:), ALLOCATABLE ::  v1d_p    !< prognostic value of v-velocity component (1d-model)
     186
     187!
     188!-- Initialize 1D model
     189    INTERFACE init_1d_model
     190       MODULE PROCEDURE init_1d_model
     191    END INTERFACE init_1d_model
     192
     193!
     194!-- Print profiles
     195    INTERFACE print_1d_model
     196       MODULE PROCEDURE print_1d_model
     197    END INTERFACE print_1d_model
     198
     199!
     200!-- Print run control information
     201    INTERFACE run_control_1d
     202       MODULE PROCEDURE run_control_1d
     203    END INTERFACE run_control_1d
     204
     205!
     206!-- Main procedure
     207    INTERFACE time_integration_1d
     208       MODULE PROCEDURE time_integration_1d
     209    END INTERFACE time_integration_1d
     210
     211!
     212!-- Calculate time step
     213    INTERFACE timestep_1d
     214       MODULE PROCEDURE timestep_1d
     215    END INTERFACE timestep_1d
     216
     217    SAVE
     218
     219    PRIVATE
     220!
     221!-- Public interfaces
     222    PUBLIC  init_1d_model
     223
     224!
     225!-- Public variables
     226    PUBLIC  damp_level_1d, damp_level_ind_1d, dt_pr_1d, dt_run_control_1d,     &
     227            e1d, end_time_1d, kh1d, km1d, l1d, rif1d, u1d, us1d, usws1d, v1d,  &
     228            vsws1d
     229
     230
     231    CONTAINS
     232
    115233 SUBROUTINE init_1d_model
    116234 
    117 
    118     USE arrays_3d,                                                             &
    119         ONLY:  l_grid, ug, u_init, vg, v_init, zu
    120    
    121     USE indices,                                                               &
    122         ONLY:  nzb, nzt
    123    
    124     USE kinds
    125    
    126     USE model_1d,                                                              &
    127         ONLY:  e1d, e1d_p, kh1d, km1d, l1d, l1d_diss, l_black, qs1d, rif1d,    &
    128                simulated_time_1d, te_e, te_em, te_u, te_um, te_v, te_vm, ts1d, &
    129                u1d, u1d_p, us1d, usws1d, v1d, v1d_p, vsws1d, z01d, z0h1d
    130    
    131     USE control_parameters,                                                    &
    132         ONLY:  constant_diffusion, constant_flux_layer, f, humidity, kappa,    &
    133                km_constant, mixing_length_1d, prandtl_number,                  &
    134                roughness_length, simulated_time_chr, z0h_factor
    135 
    136235    IMPLICIT NONE
    137236
     
    144243!
    145244!-- Allocate required 1D-arrays
    146     ALLOCATE( e1d(nzb:nzt+1),    e1d_p(nzb:nzt+1),                             &
    147               kh1d(nzb:nzt+1),   km1d(nzb:nzt+1),                              &
    148               l_black(nzb:nzt+1), l1d(nzb:nzt+1), l1d_diss(nzb:nzt+1),         &
    149               rif1d(nzb:nzt+1),   te_e(nzb:nzt+1),                             &
    150               te_em(nzb:nzt+1),  te_u(nzb:nzt+1),    te_um(nzb:nzt+1),         &
    151               te_v(nzb:nzt+1),   te_vm(nzb:nzt+1),    u1d(nzb:nzt+1),          &
    152               u1d_p(nzb:nzt+1),  v1d(nzb:nzt+1),                               &
    153               v1d_p(nzb:nzt+1) )
     245    ALLOCATE( e1d(nzb:nzt+1), e1d_p(nzb:nzt+1), kh1d(nzb:nzt+1),               &
     246              km1d(nzb:nzt+1), l_black(nzb:nzt+1), l1d(nzb:nzt+1),             &
     247              l1d_diss(nzb:nzt+1), rif1d(nzb:nzt+1), te_e(nzb:nzt+1),          &
     248              te_em(nzb:nzt+1), te_u(nzb:nzt+1), te_um(nzb:nzt+1),             &
     249              te_v(nzb:nzt+1), te_vm(nzb:nzt+1), u1d(nzb:nzt+1),               &
     250              u1d_p(nzb:nzt+1),  v1d(nzb:nzt+1), v1d_p(nzb:nzt+1) )
    154251
    155252!
     
    228325
    229326!
     327!-- Set model constant
     328    IF ( dissipation_1d == 'as_in_3d_model' )  c_m = 0.1_wp
     329
     330!
    230331!-- Set start time in hh:mm:ss - format
    231332    simulated_time_chr = time_to_string( simulated_time_1d )
     
    243344! Description:
    244345! ------------
    245 !> Leap-frog time differencing scheme for the 1D-model.
     346!> Runge-Kutta time differencing scheme for the 1D-model.
    246347!------------------------------------------------------------------------------!
    247348 
    248349 SUBROUTINE time_integration_1d
    249350
    250 
    251     USE arrays_3d,                                                             &
    252         ONLY:  dd2zu, ddzu, ddzw, l_grid, pt_init, q_init, ug, vg, zu
    253        
    254     USE control_parameters,                                                    &
    255         ONLY:  constant_diffusion, constant_flux_layer, dissipation_1d,        &
    256                humidity, intermediate_timestep_count,                          &
    257                intermediate_timestep_count_max, f, g, ibc_e_b, kappa,          & 
    258                mixing_length_1d,                                               &
    259                simulated_time_chr, timestep_scheme, tsc
    260                
    261     USE indices,                                                               &
    262         ONLY:  nzb, nzb_diff, nzt
    263        
    264     USE kinds
    265    
    266     USE model_1d,                                                              &
    267         ONLY:  current_timestep_number_1d, damp_level_ind_1d, dt_1d,           &
    268                dt_pr_1d, dt_run_control_1d, e1d, e1d_p, end_time_1d,           &
    269                kh1d, km1d, l1d, l1d_diss, l_black, qs1d, rif1d, simulated_time_1d, &
    270                stop_dt_1d, te_e, te_em, te_u, te_um, te_v, te_vm, time_pr_1d,  &
    271                ts1d, time_run_control_1d, u1d, u1d_p, us1d, usws1d, v1d,       &
    272                v1d_p, vsws1d, z01d, z0h1d
    273        
    274     USE pegrid
    275 
    276351    IMPLICIT NONE
    277352
    278353    CHARACTER (LEN=9) ::  time_to_string  !<
    279354   
    280     INTEGER(iwp) ::  k  !<
     355    INTEGER(iwp) ::  k  !< loop index
    281356   
    282     REAL(wp) ::  a            !<
    283     REAL(wp) ::  b            !<
    284     REAL(wp) ::  c_m = 0.4_wp !< model constant, 0.4 according to Detering and Etling (1985)
    285     REAL(wp) ::  dissipation  !<
    286     REAL(wp) ::  dpt_dz       !<
    287     REAL(wp) ::  flux         !<
    288     REAL(wp) ::  kmzm         !<
    289     REAL(wp) ::  kmzp         !<
    290     REAL(wp) ::  l_stable     !<
    291     REAL(wp) ::  pt_0         !<
    292     REAL(wp) ::  uv_total     !<
     357    REAL(wp) ::  a            !< auxiliary variable
     358    REAL(wp) ::  b            !< auxiliary variable
     359    REAL(wp) ::  dissipation  !< dissipation of TKE
     360    REAL(wp) ::  dpt_dz       !< vertical temperature gradient
     361    REAL(wp) ::  flux         !< vertical temperature gradient
     362    REAL(wp) ::  kmzm         !< Km(z-dz/2)
     363    REAL(wp) ::  kmzp         !< Km(z+dz/2)
     364    REAL(wp) ::  l_stable     !< mixing length for stable case
     365    REAL(wp) ::  pt_0         !< reference temperature
     366    REAL(wp) ::  uv_total     !< horizontal wind speed
    293367
    294368!
     
    759833    USE constants,                                                             &
    760834        ONLY:  pi
    761        
    762     USE indices,                                                               &
    763         ONLY:  nzb, nzt
    764        
    765     USE kinds
     835
     836    IMPLICIT NONE
     837
     838    INTEGER(iwp) ::  k     !< loop index
    766839   
    767     USE model_1d,                                                              &
    768         ONLY:  current_timestep_number_1d, dt_1d, run_control_header_1d, u1d,  &
    769                us1d, v1d
    770    
    771     USE pegrid
    772    
    773     USE control_parameters,                                                    &
    774         ONLY:  simulated_time_chr
    775 
    776     IMPLICIT NONE
    777 
    778     INTEGER(iwp) ::  k  !<
    779    
    780     REAL(wp) ::  alpha
    781     REAL(wp) ::  energy
    782     REAL(wp) ::  umax
    783     REAL(wp) ::  uv_total
    784     REAL(wp) ::  vmax
     840    REAL(wp) ::  alpha     !< angle of wind vector at top of constant-flux layer
     841    REAL(wp) ::  energy    !< kinetic energy
     842    REAL(wp) ::  umax      !< maximum of u
     843    REAL(wp) ::  uv_total  !< horizontal wind speed
     844    REAL(wp) ::  vmax      !< maximum of v
    785845
    786846!
     
    844904 SUBROUTINE timestep_1d
    845905
    846 
    847     USE arrays_3d,                                                             &
    848         ONLY:  dzu, zu
    849        
    850     USE indices,                                                               &
    851         ONLY:  nzb, nzt
    852    
    853     USE kinds
    854    
    855     USE model_1d,                                                              &
    856         ONLY:  dt_1d, dt_max_1d, km1d, stop_dt_1d
    857    
    858     USE pegrid
    859    
    860     USE control_parameters,                                                    &
    861         ONLY:  message_string
    862 
    863906    IMPLICIT NONE
    864907
    865     INTEGER(iwp) ::  k !<
    866    
    867     REAL(wp) ::  div      !<
    868     REAL(wp) ::  dt_diff  !<
    869     REAL(wp) ::  fac      !<
    870     REAL(wp) ::  value    !<
    871 
     908    INTEGER(iwp) ::  k    !< loop index
     909
     910    REAL(wp) ::  dt_diff  !< time step accorind to diffusion criterion
     911    REAL(wp) ::  fac      !< factor of criterion
     912    REAL(wp) ::  value    !< auxiliary variable
    872913
    873914!
     
    906947 SUBROUTINE print_1d_model
    907948
    908 
    909     USE arrays_3d,                                                             &
    910         ONLY:  pt_init, zu
    911        
    912     USE indices,                                                               &
    913         ONLY:  nzb, nzt
    914        
    915     USE kinds
    916    
    917     USE model_1d,                                                              &
    918         ONLY:  e1d, kh1d, km1d, l1d, rif1d, u1d, v1d
    919    
    920     USE pegrid
    921    
    922     USE control_parameters,                                                    &
    923         ONLY:  run_description_header, simulated_time_chr
    924 
    925949    IMPLICIT NONE
    926950
    927 
    928     INTEGER(iwp) ::  k  !<
     951    INTEGER(iwp) ::  k  !< loop parameter
     952
     953    LOGICAL, SAVE :: write_first = .TRUE. !< flag for writing header
    929954
    930955
     
    936961!
    937962!--    Write Header
    938        WRITE ( 17, 100 )  TRIM( run_description_header ), &
    939                           TRIM( simulated_time_chr )
     963       IF ( write_first )  THEN
     964          WRITE ( 17, 100 )  TRIM( run_description_header )
     965          write_first = .FALSE.
     966       ENDIF
     967
     968!
     969!--    Write the values
     970       WRITE ( 17, 104 )  TRIM( simulated_time_chr )
    940971       WRITE ( 17, 101 )
    941 
    942 !
    943 !--    Write the values
    944972       WRITE ( 17, 102 )
    945973       WRITE ( 17, 101 )
     
    960988!
    961989!-- Formats
    962 100 FORMAT (//1X,A/1X,10('-')/' 1d-model profiles'/ &
    963             ' Time: ',A)
    964 101 FORMAT (1X,79('-'))
    965 102 FORMAT ('   k     zu      u      v     pt      e    rif    Km    Kh     ', &
     990100 FORMAT ('# ',A/'#',10('-')/'# 1d-model profiles')
     991104 FORMAT (//'# Time: ',A)
     992101 FORMAT ('#',79('-'))
     993102 FORMAT ('#  k     zu      u      v     pt      e    rif    Km    Kh     ', &
    966994            'l      zu      k')
    967995103 FORMAT (1X,I4,1X,F7.1,1X,F6.2,1X,F6.2,1X,F6.2,1X,F6.2,1X,F5.2,1X,F5.2, &
     
    970998
    971999 END SUBROUTINE print_1d_model
     1000
     1001
     1002 END MODULE
Note: See TracChangeset for help on using the changeset viewer.