Ignore:
Timestamp:
Mar 20, 2014 8:40:49 AM (10 years ago)
Author:
raasch
Message:

ONLY-attribute added to USE-statements,
kind-parameters added to all INTEGER and REAL declaration statements,
kinds are defined in new module kinds,
old module precision_kind is removed,
revision history before 2012 removed,
comment fields (!:) to be used for variable explanations added to all variable declaration statements

File:
1 edited

Legend:

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

    r1319 r1320  
    2020! Current revisions:
    2121! -----------------
    22 !
     22! ONLY-attribute added to USE-statements,
     23! kind-parameters added to all INTEGER and REAL declaration statements,
     24! kinds are defined in new module kinds,
     25! revision history before 2012 removed,
     26! comment fields (!:) to be used for variable explanations added to
     27! all variable declaration statements
    2328!
    2429! Former revisions:
     
    3439! 964 2012-07-26 09:14:24Z raasch
    3540! code for profil-output removed
    36 !
    37 ! 291 2009-04-16 12:07:26Z raasch
    38 ! simulated_time in NetCDF output replaced by time_since_reference_point.
    39 ! Output of NetCDF messages with aid of message handling routine.
    40 ! Output of messages replaced by message handling routine.
    41 !
    42 ! 189 2008-08-13 17:09:26Z letzel
    43 ! allow 100 spectra levels instead of 10 for consistency with
    44 ! define_netcdf_header, +user-defined spectra
    45 !
    46 ! February 2007
    47 ! RCS Log replace by Id keyword, revision history cleaned up
    48 !
    49 ! Revision 1.7  2006/04/11 14:56:38  raasch
    50 ! pl_spectra renamed data_output_sp
    5141!
    5242! Revision 1.1  2001/01/05 15:14:20  raasch
     
    6151#if defined( __spectra )
    6252
    63     USE arrays_3d
    64     USE control_parameters
    65     USE cpulog
     53    USE control_parameters,                                                    &
     54        ONLY:  average_count_sp, averaging_interval_sp, dosp_time_count
     55
     56    USE cpulog,                                                                &
     57        ONLY:  cpu_log, log_point
     58
     59    USE kinds
     60
    6661    USE netcdf_control
     62
    6763    USE pegrid
    68     USE spectrum
    69     USE statistics
     64
     65    USE spectrum,                                                              &
     66        ONLY:  data_output_sp
     67
     68    USE statistics,                                                            &
     69        ONLY:  spectrum_x, spectrum_y
    7070
    7171
    7272    IMPLICIT NONE
    7373
    74     INTEGER :: m, pr, cranz_x, cranz_y
    75     LOGICAL :: frame_x, frame_y
     74    INTEGER(iwp) ::  cranz_x !:
     75    INTEGER(iwp) ::  cranz_y !:
     76    INTEGER(iwp) ::  m       !:
     77    INTEGER(iwp) ::  pr      !:
     78   
     79    LOGICAL      ::  frame_x !:
     80    LOGICAL      ::  frame_y !:
    7681
    7782    CALL cpu_log( log_point(31), 'data_output_spectra', 'start' )
     
    183188#if defined( __netcdf )
    184189
    185     USE constants
    186     USE control_parameters
    187     USE grid_variables
    188     USE indices
     190    USE constants,                                                             &
     191        ONLY:  pi
     192
     193    USE control_parameters,                                                    &
     194        ONLY:  dosp_time_count
     195
     196    USE grid_variables,                                                        &
     197        ONLY:  dx, dy
     198
     199    USE indices,                                                               &
     200        ONLY:  nx, ny
     201
     202    USE kinds
     203
    189204    USE netcdf_control
    190     USE spectrum
    191     USE statistics
     205
     206    USE spectrum,                                                              &
     207        ONLY:  n_sp_x, n_sp_y
     208
     209    USE statistics,                                                            &
     210        ONLY:  spectrum_x, spectrum_y
    192211
    193212    IMPLICIT NONE
    194213
    195     CHARACTER (LEN=1), INTENT(IN) ::  direction
    196 
    197     INTEGER, INTENT(IN) ::  nsp
    198 
    199     INTEGER ::  i, k
    200 
    201     REAL ::  frequency
    202 
    203     REAL, DIMENSION(nx/2) ::  netcdf_data_x
    204     REAL, DIMENSION(ny/2) ::  netcdf_data_y
     214    CHARACTER (LEN=1), INTENT(IN) ::  direction     !:
     215
     216    INTEGER(iwp), INTENT(IN)      ::  nsp           !:
     217
     218    INTEGER(iwp)                  ::  i             !:
     219    INTEGER(iwp)                  ::  k             !:
     220
     221    REAL(wp)                      ::  frequency     !:
     222
     223    REAL(wp), DIMENSION(nx/2)     ::  netcdf_data_x !:
     224    REAL(wp), DIMENSION(ny/2)     ::  netcdf_data_y !:
    205225
    206226
     
    248268 SUBROUTINE data_output_spectra_x( m, cranz, pr, frame_written )
    249269
    250     USE arrays_3d
    251     USE constants
    252     USE control_parameters
    253     USE grid_variables
    254     USE indices
     270    USE constants,                                                             &
     271        ONLY:  pi
     272
     273    USE control_parameters,                                                    &
     274        ONLY:  averaging_interval_sp
     275
     276    USE grid_variables,                                                        &
     277        ONLY:  dx
     278
     279    USE indices,                                                               &
     280        ONLY:  nx
     281
     282    USE kinds
     283
    255284    USE pegrid
    256     USE singleton
    257     USE spectrum
    258     USE statistics
    259     USE transpose_indices
     285
     286    USE spectrum,                                                              &
     287        ONLY:  comp_spectra_level, n_sp_x, plot_spectra_level
    260288
    261289    IMPLICIT NONE
    262290
    263     CHARACTER (LEN=30) ::  atext
    264     INTEGER            ::  i, j, k, m, pr
    265     LOGICAL            ::  frame_written
    266     REAL               ::  frequency = 0.0
    267 
     291    CHARACTER (LEN=30) ::  atext !:
     292   
     293    INTEGER(iwp)       ::  i     !:
     294    INTEGER(iwp)       ::  j     !:
     295    INTEGER(iwp)       ::  k     !:
     296    INTEGER(iwp)       ::  m     !:
     297    INTEGER(iwp)       ::  pr    !:
     298   
     299    LOGICAL            ::  frame_written   !:
     300   
     301    REAL(wp)           ::  frequency = 0.0 !:
    268302!
    269303!-- Variables needed for PROFIL-namelist
    270     INTEGER                  :: cranz, labforx = 3, labfory = 3, legpos = 3, &
    271                                 timodex = 1
    272     INTEGER, DIMENSION(1:100):: cucol = 1, klist = 999999, lstyle = 0
    273     LOGICAL                  :: datleg = .TRUE., grid = .TRUE., &
    274                                 lclose = .TRUE., rand = .TRUE., &
    275                                 swap = .TRUE., twoxa = .TRUE.,  &
    276                                 xlog = .TRUE., ylog = .TRUE.
    277     CHARACTER (LEN=80)       :: rtext, utext, xtext = 'k in m>->1', ytext
    278     REAL                     :: gwid = 0.1, rlegfak = 0.7, uxmin, uxmax, &
    279                                 uymin, uymax
    280     REAL, DIMENSION(1:100)   :: lwid = 0.6
    281     REAL, DIMENSION(100)     :: uyma, uymi
     304    CHARACTER (LEN=80) ::  rtext                !:
     305    CHARACTER (LEN=80) ::  utext                !:
     306    CHARACTER (LEN=80) ::  xtext = 'k in m>->1' !:
     307    CHARACTER (LEN=80) ::  ytext                !:
     308
     309    INTEGER(iwp)       ::  cranz       !:
     310    INTEGER(iwp)       ::  labforx = 3 !:
     311    INTEGER(iwp)       ::  labfory = 3 !:
     312    INTEGER(iwp)       ::  legpos  = 3 !:
     313    INTEGER(iwp)       ::  timodex = 1 !:
     314   
     315    INTEGER(iwp), DIMENSION(1:100) ::  cucol  = 1      !:
     316    INTEGER(iwp), DIMENSION(1:100) ::  klist  = 999999 !:
     317    INTEGER(iwp), DIMENSION(1:100) ::  lstyle = 0      !:
     318   
     319    LOGICAL ::  datleg = .TRUE. !:
     320    LOGICAL ::  grid = .TRUE.   !:
     321    LOGICAL ::  lclose = .TRUE. !:
     322    LOGICAL ::  rand = .TRUE.   !:
     323    LOGICAL ::  swap = .TRUE.   !:
     324    LOGICAL ::  twoxa = .TRUE.  !:
     325    LOGICAL ::  xlog = .TRUE.   !:
     326    LOGICAL ::  ylog = .TRUE.   !:
     327   
     328    REAL(wp) ::  gwid = 0.1    !:
     329    REAL(wp) ::  rlegfak = 0.7 !:
     330    REAL(wp) ::  uxmin         !:
     331    REAL(wp) ::  uxmax         !:
     332    REAL(wp) ::  uymin         !:
     333    REAL(wp) ::  uymax         !:
     334     
     335    REAL(wp), DIMENSION(1:100) ::  lwid = 0.6 !:
     336    REAL(wp), DIMENSION(100)   ::  uyma       !:
     337    REAL(wp), DIMENSION(100)   ::  uymi       !:
    282338
    283339    NAMELIST /RAHMEN/  cranz, datleg, rtext, swap
     
    407463 SUBROUTINE data_output_spectra_y( m, cranz, pr, frame_written )
    408464
    409     USE arrays_3d
    410     USE constants
    411     USE control_parameters
    412     USE grid_variables
    413     USE indices
     465    USE constants,                                                             &
     466        ONLY:  pi
     467
     468    USE control_parameters,                                                    &
     469        ONLY:  averaging_interval_sp
     470
     471    USE grid_variables,                                                        &
     472        ONLY:  dy
     473
     474    USE indices,                                                               &
     475        ONLY:  ny
     476
     477    USE kinds
     478
    414479    USE pegrid
    415     USE singleton
    416     USE spectrum
    417     USE statistics
    418     USE transpose_indices
     480
     481    USE spectrum  comp_spectra_level, plot_spectra_level
    419482
    420483    IMPLICIT NONE
    421484
    422     CHARACTER (LEN=30) ::  atext
    423     INTEGER            :: i, j, k, m, pr
    424     LOGICAL            :: frame_written
    425     REAL               :: frequency = 0.0
     485   
     486    CHARACTER (LEN=30) ::  atext !:
     487   
     488    INTEGER(iwp)       ::  i     !:
     489    INTEGER(iwp)       ::  j     !:
     490    INTEGER(iwp)       ::  k     !:
     491    INTEGER(iwp)       ::  m     !:
     492    INTEGER(iwp)       ::  pr    !:
     493   
     494    LOGICAL            :: frame_written   !:
     495   
     496    REAL(wp)           :: frequency = 0.0 !:
    426497
    427498!
    428499!-- Variables needed for PROFIL-namelist
    429     INTEGER                  :: cranz, labforx = 3, labfory = 3, legpos = 3, &
    430                                 timodex = 1
    431     INTEGER, DIMENSION(1:100):: cucol = 1, klist = 999999, lstyle = 0
    432     LOGICAL                  :: datleg = .TRUE., grid = .TRUE., &
    433                                 lclose = .TRUE., rand = .TRUE., &
    434                                 swap = .TRUE., twoxa = .TRUE.,  &
    435                                 xlog = .TRUE., ylog = .TRUE.
    436     CHARACTER (LEN=80)       :: rtext, utext, xtext = 'k in m>->1', ytext
    437     REAL                     :: gwid = 0.1, rlegfak = 0.7, uxmin, uxmax, &
    438                                 uymin, uymax
    439     REAL, DIMENSION(1:100)   :: lwid = 0.6
    440     REAL, DIMENSION(100)     :: uyma, uymi
     500    CHARACTER (LEN=80) ::  rtext                !:
     501    CHARACTER (LEN=80) ::  utext                !:
     502    CHARACTER (LEN=80) ::  xtext = 'k in m>->1' !:
     503    CHARACTER (LEN=80) ::  ytext                !:
     504
     505    INTEGER(iwp) ::  cranz       !:
     506    INTEGER(iwp) ::  labforx = 3 !:
     507    INTEGER(iwp) ::  labfory = 3 !:
     508    INTEGER(iwp) ::  legpos  = 3 !:
     509    INTEGER(iwp) ::  timodex = 1 !:
     510   
     511    INTEGER(iwp), DIMENSION(1:100) ::  cucol  = 1      !:
     512    INTEGER(iwp), DIMENSION(1:100) ::  klist  = 999999 !:
     513    INTEGER(iwp), DIMENSION(1:100) ::  lstyle = 0      !:
     514   
     515    LOGICAL ::  datleg = .TRUE. !:
     516    LOGICAL ::  grid = .TRUE.   !:
     517    LOGICAL ::  lclose = .TRUE. !:
     518    LOGICAL ::  rand = .TRUE.   !:
     519    LOGICAL ::  swap = .TRUE.   !:
     520    LOGICAL ::  twoxa = .TRUE.  !:
     521    LOGICAL ::  xlog = .TRUE.   !:
     522    LOGICAL ::  ylog = .TRUE.   !:
     523   
     524    REAL(wp) ::  gwid = 0.1     !:
     525    REAL(wp) ::  rlegfak = 0.7  !:
     526    REAL(wp) ::  uxmin          !:
     527    REAL(wp) ::  uxmax          !:
     528    REAL(wp) ::  uymin          !:
     529    REAL(wp) ::  uymax          !:
     530   
     531    REAL(wp), DIMENSION(1:100) ::  lwid = 0.6 !:
     532   
     533    REAL(wp), DIMENSION(100)   ::  uyma       !:
     534    REAL(wp), DIMENSION(100)   ::  uymi       !:
    441535
    442536    NAMELIST /RAHMEN/  cranz, datleg, rtext, swap
Note: See TracChangeset for help on using the changeset viewer.