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/header.f90

    r1497 r1551  
    2020! Current revisions:
    2121! -----------------
    22 !
     22! Added informal output for land surface model and radiation model. Removed typo.
    2323!
    2424! Former revisions:
     
    170170! Description:
    171171! ------------
    172 ! Writing a header with all important informations about the actual run.
     172! Writing a header with all important information about the actual run.
    173173! This subroutine is called three times, two times at the beginning
    174174! (writing information on files RUN_CONTROL and HEADER) and one time at the
     
    200200       
    201201    USE kinds
    202    
     202   
     203    USE land_surface_model_mod,                                                &
     204        ONLY:  conserve_water_content, dewfall, land_surface, nzb_soil,        &
     205               nzt_soil, root_fraction, soil_moisture, soil_temperature,       &
     206               soil_type, soil_type_name, veg_type, veg_type_name, zs
     207 
    203208    USE model_1d,                                                              &
    204209        ONLY:  damp_level_ind_1d, dt_pr_1d, dt_run_control_1d, end_time_1d
     
    225230               lai_beta, leaf_scalar_exch_coeff, leaf_surface_conc, pch_index, &
    226231               plant_canopy
     232
     233    USE radiation_model_mod,                                                   &
     234        ONLY:  albedo, day_init, dt_radiation, lambda, net_radiation,          &
     235               radiation, radiation_scheme, time_utc_init
    227236   
    228237    USE spectrum,                                                              &
     
    263272    CHARACTER (LEN=86) ::  gradients           !:
    264273    CHARACTER (LEN=86) ::  leaf_area_density   !:
     274    CHARACTER (LEN=86) ::  roots               !:
    265275    CHARACTER (LEN=86) ::  slices              !:
    266276    CHARACTER (LEN=86) ::  temperatures        !:
     
    311321!
    312322!-- At the end of the run, output file (HEADER) will be rewritten with
    313 !-- new informations
     323!-- new information
    314324    IF ( io == 19 .AND. simulated_time_at_begin /= simulated_time ) REWIND( 19 )
    315325
     
    495505
    496506!
    497 !-- Runtime and timestep informations
     507!-- Runtime and timestep information
    498508    WRITE ( io, 200 )
    499509    IF ( .NOT. dt_fixed )  THEN
     
    850860
    851861
     862    IF ( land_surface )  THEN
     863
     864       temperatures = ''
     865       gradients    = '' ! use for humidity here
     866       coordinates  = '' ! use for height
     867       roots        = '' ! use for root fraction
     868       slices       = '' ! use for index
     869
     870       i = 1
     871       DO i = nzb_soil, nzt_soil
     872          WRITE (coor_chr,'(F10.2,7X)') soil_temperature(i)
     873          temperatures = TRIM( temperatures ) // ' ' // TRIM( coor_chr )
     874
     875          WRITE (coor_chr,'(F10.2,7X)') soil_moisture(i)
     876          gradients = TRIM( gradients ) // ' ' // TRIM( coor_chr )
     877
     878          WRITE (coor_chr,'(F10.2,7X)')  - zs(i)
     879          coordinates = TRIM( coordinates ) // ' '  // TRIM( coor_chr )
     880
     881          WRITE (coor_chr,'(F10.2,7X)')  root_fraction(i)
     882          roots = TRIM( roots ) // ' '  // TRIM( coor_chr )
     883
     884          WRITE (coor_chr,'(I10,7X)')  i
     885          slices = TRIM( slices ) // ' '  // TRIM( coor_chr )
     886
     887
     888       ENDDO
     889
     890!
     891!--    Write land surface model header
     892       WRITE( io, 419 )
     893       IF ( conserve_water_content )  THEN
     894          WRITE( io, 440 )
     895       ELSE
     896          WRITE( io, 441 )
     897       ENDIF
     898
     899       IF ( dewfall )  THEN
     900          WRITE( io, 442 )
     901       ELSE
     902          WRITE( io, 443 )
     903       ENDIF
     904
     905       WRITE( io, 438 ) veg_type_name(veg_type), soil_type_name(soil_type)
     906       WRITE( io, 439 ) TRIM( coordinates ), TRIM( temperatures ),             &
     907                        TRIM( gradients ), TRIM( roots ), TRIM( slices )
     908
     909
     910    ENDIF
     911
     912    IF ( radiation )  THEN
     913!
     914!--    Write land surface model header
     915       WRITE( io, 444 )
     916
     917       IF ( radiation_scheme == "constant" )  THEN
     918          WRITE( io, 445 ) net_radiation
     919       ELSEIF ( radiation_scheme == "clear-sky" )  THEN
     920          WRITE( io, 446 )
     921       ELSE
     922          WRITE( io, 447 ) radiation_scheme
     923       ENDIF
     924
     925       WRITE( io, 448 ) albedo
     926       WRITE( io, 449 ) dt_radiation
     927
     928    ENDIF
     929
     930
    852931!
    853932!-- Boundary conditions
     
    877956
    878957    IF ( ibc_pt_b == 0 )  THEN
    879        runten = TRIM( runten ) // ' pt(0)   = pt_surface'
     958       IF ( land_surface )  THEN
     959          runten = TRIM( runten ) // ' pt(0)     = from soil model'
     960       ELSE
     961          runten = TRIM( runten ) // ' pt(0)     = pt_surface'
     962       ENDIF
    880963    ELSEIF ( ibc_pt_b == 1 )  THEN
    881        runten = TRIM( runten ) // ' pt(0)   = pt(1)'
     964       runten = TRIM( runten ) // ' pt(0)     = pt(1)'
    882965    ELSEIF ( ibc_pt_b == 2 )  THEN
    883        runten = TRIM( runten ) // ' pt(0) = from coupled model'
     966       runten = TRIM( runten ) // ' pt(0)     = from coupled model'
    884967    ENDIF
    885968    IF ( ibc_pt_t == 0 )  THEN
     
    9181001    IF ( humidity )  THEN
    9191002       IF ( ibc_q_b == 0 )  THEN
    920           runten = 'q(0)     = q_surface'
     1003          IF ( land_surface )  THEN
     1004             runten = 'q(0)     = from soil model'
     1005          ELSE
     1006             runten = 'q(0)     = q_surface'
     1007          ENDIF
     1008
    9211009       ELSE
    9221010          runten = 'q(0)     = q(1)'
     
    12251313             coordinates = '/'
    12261314!
    1227 !--          Building strings with index and coordinate informations of the
     1315!--          Building strings with index and coordinate information of the
    12281316!--          slices
    12291317             DO  WHILE ( section(i,1) /= -9999 )
     
    12711359             coordinates = '/'
    12721360!
    1273 !--          Building strings with index and coordinate informations of the
     1361!--          Building strings with index and coordinate information of the
    12741362!--          slices
    12751363             DO  WHILE ( section(i,2) /= -9999 )
     
    13131401             coordinates = '/'
    13141402!
    1315 !--          Building strings with index and coordinate informations of the
     1403!--          Building strings with index and coordinate information of the
    13161404!--          slices
    13171405             DO  WHILE ( section(i,3) /= -9999 )
     
    15711659!
    15721660!-- Geostrophic parameters
    1573     WRITE ( io, 410 )  omega, phi, f, fs
     1661    IF ( radiation .AND. radiation_scheme /= 'constant' )  THEN
     1662       WRITE ( io, 417 )  lambda
     1663    ENDIF
     1664    WRITE ( io, 410 )  phi, omega, f, fs
    15741665
    15751666!
    15761667!-- Other quantities
    15771668    WRITE ( io, 411 )  g
     1669    IF ( radiation .AND. radiation_scheme /= 'constant' )  THEN
     1670       WRITE ( io, 418 )  day_init, time_utc_init
     1671    ENDIF
     1672
    15781673    WRITE ( io, 412 )  TRIM( reference_state )
    15791674    IF ( use_single_reference_value )  THEN
     
    17321827
    17331828!
    1734 !-- User-defined informations
     1829!-- User-defined information
    17351830    CALL user_header( io )
    17361831
     
    18671962260 FORMAT (/' The model has a slope in x-direction. Inclination angle: ',F6.2,&
    18681963             ' degrees')
    1869 270 FORMAT (//' Topography informations:'/ &
    1870               ' -----------------------'// &
     1964270 FORMAT (//' Topography information:'/ &
     1965              ' ----------------------'// &
    18711966              1X,'Topography: ',A)
    18721967271 FORMAT (  ' Building size (x/y/z) in m: ',F5.1,' / ',F5.1,' / ',F5.1/ &
     
    19052000             ' -------------------'// &
    19062001             '                     p                    uv             ', &
    1907              '                   pt'// &
     2002             '                     pt'// &
    19082003             ' B. bound.: ',A/ &
    19092004             ' T. bound.: ',A)
     
    20472142400 FORMAT (//' Physical quantities:'/ &
    20482143              ' -------------------'/)
    2049 410 FORMAT ('    Angular velocity    :   omega = ',E9.3,' rad/s'/  &
    2050             '    Geograph. latitude  :   phi   = ',F4.1,' degr'/   &
    2051             '    Coriolis parameter  :   f     = ',F9.6,' 1/s'/    &
    2052             '                            f*    = ',F9.6,' 1/s')
    2053 411 FORMAT (/'    Gravity             :   g     = ',F4.1,' m/s**2')
     2144410 FORMAT ('    Geograph. latitude  :   phi    = ',F4.1,' degr'/   &
     2145            '    Angular velocity    :   omega  = ',E9.3,' rad/s'/  &
     2146            '    Coriolis parameter  :   f      = ',F9.6,' 1/s'/    &
     2147            '                            f*     = ',F9.6,' 1/s')
     2148411 FORMAT (/'    Gravity             :   g      = ',F4.1,' m/s**2')
    20542149412 FORMAT (/'    Reference state used in buoyancy terms: ',A)
    20552150413 FORMAT ('       Reference density in buoyancy terms: ',F8.3,' kg/m**3')
    20562151414 FORMAT ('       Reference temperature in buoyancy terms: ',F8.4,' K')
    2057 415 FORMAT (/'    Cloud physics parameters:'/ &
    2058              '    ------------------------'/)
    2059 416 FORMAT ('        Surface pressure   :   p_0   = ',F7.2,' hPa'/      &
    2060             '        Gas constant       :   R     = ',F5.1,' J/(kg K)'/ &
    2061             '        Density of air     :   rho_0 = ',F5.3,' kg/m**3'/  &
    2062             '        Specific heat cap. :   c_p   = ',F6.1,' J/(kg K)'/ &
    2063             '        Vapourization heat :   L_v   = ',E8.2,' J/kg')
     2152415 FORMAT (/' Cloud physics parameters:'/ &
     2153             ' ------------------------'/)
     2154416 FORMAT ('    Surface pressure   :   p_0   = ',F7.2,' hPa'/      &
     2155            '    Gas constant       :   R     = ',F5.1,' J/(kg K)'/ &
     2156            '    Density of air     :   rho_0 = ',F5.3,' kg/m**3'/  &
     2157            '    Specific heat cap. :   c_p   = ',F6.1,' J/(kg K)'/ &
     2158            '    Vapourization heat :   L_v   = ',E8.2,' J/kg')
     2159417 FORMAT ('    Geograph. longitude :   lambda = ',F4.1,' degr')
     2160418 FORMAT (/'    Day of the year at model start :   day_init      =     ',I3 &
     2161            /'    UTC time at model start        :   time_utc_init = ',F7.1' s')
     2162419 FORMAT (//' Land surface model information:'/ &
     2163              ' ------------------------------'/)
    20642164420 FORMAT (/'    Characteristic levels of the initial temperature profile:'// &
    20652165            '       Height:        ',A,'  m'/ &
     
    21202220                       '[0,1000] cm**2/s**3')
    21212221437 FORMAT ('    Droplet collision is switched off')
     2222438 FORMAT (' --> Land surface type  : ',A,/ &
     2223            ' --> Soil porosity type : ',A)
     2224439 FORMAT (/'    Initial soil temperature and moisture profile:'// &
     2225            '       Height:        ',A,'  m'/ &
     2226            '       Temperature:   ',A,'  K'/ &
     2227            '       Moisture:      ',A,'  m**3/m**3'/ &
     2228            '       Root fraction: ',A,'  '/ &
     2229            '       Gridpoint:     ',A)
     2230440 FORMAT (/' --> Dewfall is allowed (default)')
     2231441 FORMAT (' --> Dewfall is inhibited')
     2232442 FORMAT (' --> Soil bottom is closed (water content is conserved, default)')
     2233443 FORMAT (' --> Soil bottom is open (water content is not conserved)')
     2234444 FORMAT (//' Radiation model information:'/                                 &
     2235              ' ----------------------------'/)
     2236445 FORMAT (' --> Using constant net radiation: net_radiation = ', F6.2, '  W/m**2')
     2237446 FORMAT (' --> Simple radiation scheme for clear sky is used (no clouds,',  &
     2238                   ' default)')
     2239447 FORMAT (' --> Radiation scheme:', A)
     2240448 FORMAT (/'    Surface albedo: albedo = ', F5.3)
     2241449 FORMAT  ('    Timestep: dt_radiation = ', F5.2, '  s')
     2242
    21222243450 FORMAT (//' LES / Turbulence quantities:'/ &
    21232244              ' ---------------------------'/)
     
    22002321508 FORMAT ('    Ventilation effects on evaporation of rain drops')
    22012322509 FORMAT ('    Slope limiter used for sedimentation process')
    2202 510 FORMAT ('        Droplet density    :   N_c   = ',F6.1,' 1/cm**3')
    2203 511 FORMAT ('        Sedimentation Courant number:                  '/&
     2323510 FORMAT ('    Droplet density    :   N_c   = ',F6.1,' 1/cm**3')
     2324511 FORMAT ('    Sedimentation Courant number:                  '/&
    22042325            '                               C_s   = ',F3.1,'        ')
    22052326512 FORMAT (/' Date:                 ',A8,6X,'Run:       ',A20/      &
Note: See TracChangeset for help on using the changeset viewer.