Ignore:
Timestamp:
Dec 10, 2018 1:25:22 PM (5 years ago)
Author:
eckhard
Message:

inifor: Prefixed all INIFOR modules with inifor_ and removed unused variables

Location:
palm/trunk/UTIL/inifor/src
Files:
8 edited

Legend:

Unmodified
Added
Removed
  • palm/trunk/UTIL/inifor/src/inifor.f90

    r3615 r3618  
    2626! -----------------
    2727! $Id$
     28! Prefixed all INIFOR modules with inifor_
     29!
     30!
     31! 3615 2018-12-10 07:21:03Z raasch
    2832! bugfix: abort replaced by inifor_abort
    2933!
     
    7478 PROGRAM inifor
    7579
    76     USE control
    77     USE defs
    78     USE grid,                                                                  &
     80    USE inifor_control
     81    USE inifor_defs
     82    USE inifor_grid,                                                           &
    7983        ONLY:  setup_parameters, setup_grids, setup_variable_tables,           &
    8084               setup_io_groups, fini_grids, fini_variables, fini_io_groups,    &
     
    8488               averaging_width_ns, averaging_width_ew, phi_n, lambda_n,        &
    8589               lam_centre, phi_centre
    86     USE io
    87     USE transform,                                                             &
     90    USE inifor_io
     91    USE inifor_transform,                                                      &
    8892        ONLY:  average_profile, interpolate_2d, interpolate_3d,                &
    8993               geostrophic_winds, extrapolate_density, extrapolate_pressure,   &
    9094               get_surface_pressure
    91     USE types
     95    USE inifor_types
    9296   
    9397    IMPLICIT NONE
  • palm/trunk/UTIL/inifor/src/inifor_control.f90

    r3614 r3618  
    2626! -----------------
    2727! $Id$
     28! Prefixed all INIFOR modules with inifor_
     29!
     30!
     31! 3614 2018-12-10 07:05:46Z raasch
    2832! abort renamed inifor_abort to avoid intrinsic problem in Fortran
    2933!
     
    5862!> feedback to the terminal and a log file.
    5963!------------------------------------------------------------------------------!
    60  MODULE control
    61 
    62     USE defs,                                                                  &
     64 MODULE inifor_control
     65
     66    USE inifor_defs,                                                           &
    6367        ONLY:  LNAME, dp, VERSION, COPYRIGHT
    6468
    65     USE util,                                                                  &
     69    USE inifor_util,                                                           &
    6670        ONLY:  real_to_str, real_to_str_f
    6771
     
    258262    END SUBROUTINE run_control
    259263
    260  END MODULE
    261 
     264 END MODULE inifor_control
     265
  • palm/trunk/UTIL/inifor/src/inifor_defs.f90

    r3613 r3618  
    2626! -----------------
    2727! $Id$
     28! Prefixed module with inifor_
     29!
     30!
     31! 3613 2018-12-07 18:20:37Z eckhard
    2832! Bumped version number
    2933!
     
    7377!> The defs module provides global constants used in INIFOR.
    7478!------------------------------------------------------------------------------!
    75  MODULE defs
     79 MODULE inifor_defs
    7680 
    7781 IMPLICIT NONE
     
    127131     ACHAR( 10 ) // ' Copyright 2017-2018 Deutscher Wetterdienst Offenbach' !< Copyright notice
    128132
    129  END MODULE defs
     133 END MODULE inifor_defs
  • palm/trunk/UTIL/inifor/src/inifor_grid.f90

    r3615 r3618  
    2626! -----------------
    2727! $Id$
     28! Prefixed all INIFOR modules with inifor_, removed unused variables
     29!
     30!
     31! 3615 2018-12-10 07:21:03Z raasch
    2832! bugfix: abort replaced by inifor_abort
    2933!
     
    97101!------------------------------------------------------------------------------!
    98102
    99  MODULE grid
    100 
    101     USE control
    102     USE defs,                                                                  &
     103 MODULE inifor_grid
     104
     105    USE inifor_control
     106    USE inifor_defs,                                                           &
    103107        ONLY:  DATE, EARTH_RADIUS, TO_RADIANS, TO_DEGREES, PI, dp, hp, sp,     &
    104108               SNAME, LNAME, PATH, FORCING_STEP, WATER_ID, FILL_ITERATIONS,    &
    105109               BETA, P_SL, T_SL, BETA, RD, RV, G, P_REF, RD_PALM, CP_PALM,     &
    106110               RHO_L, OMEGA, HECTO
    107     USE io,                                                                    &
     111    USE inifor_io,                                                             &
    108112        ONLY:  get_netcdf_attribute, get_netcdf_dim_vector,                    &
    109113               get_netcdf_variable, parse_command_line_arguments,              &
    110114               validate_config
    111     USE netcdf,                                                                &
    112         ONLY:  NF90_MAX_NAME, NF90_MAX_VAR_DIMS
    113     USE transform,                                                             &
     115    USE inifor_transform,                                                      &
    114116        ONLY:  average_2d, rotate_to_cosmo, find_horizontal_neighbours,&
    115117               compute_horizontal_interp_weights,                              &
     
    119121               project, centre_velocities, phi2phirot, rla2rlarot, uv2uvrot,   &
    120122               phirot2phi, rlarot2rla
    121     USE types
    122     USE util
     123    USE inifor_types
     124    USE inifor_util
     125    USE netcdf,                                                                &
     126        ONLY:  NF90_MAX_NAME, NF90_MAX_VAR_DIMS
    123127   
    124128    IMPLICIT NONE
     
    628632       phirot = project(0.5_dp*ly, y0, EARTH_RADIUS) * TO_DEGREES,             &
    629633       rlarot = project(0.5_dp*lx, x0, EARTH_RADIUS) * TO_DEGREES,             &
    630        polphi = phi_cn * TO_DEGREES, pollam = lambda_cn * TO_DEGREES,          &
     634       polphi = phi_cn * TO_DEGREES,                                           &
    631635       polgam = gam * TO_DEGREES                                               &
    632636    ) * TO_RADIANS
     
    660664    f3 = 2.0_dp * OMEGA * SIN(                                                 &
    661665       TO_RADIANS*phirot2phi( phi_centre * TO_DEGREES, lam_centre * TO_DEGREES,&
    662                               phi_n * TO_DEGREES, lambda_n * TO_DEGREES,       &
     666                              phi_n * TO_DEGREES,                              &
    663667                              gam * TO_DEGREES )                               &
    664668       )
     
    18251829       IF ( number_stretch_level_end >= 1 ) THEN
    18261830          CALL calculate_stretching_factor( number_stretch_level_end, dz,      &
    1827                                             dz_stretch_factor,                 &
    18281831                                            dz_stretch_factor_array,           &   
    18291832                                            dz_stretch_level_end,              &
     
    19031906!> results into an overdetermined system.
    19041907!------------------------------------------------------------------------------!
    1905  SUBROUTINE calculate_stretching_factor( number_end, dz, dz_stretch_factor,    &
     1908 SUBROUTINE calculate_stretching_factor( number_end, dz,                       &
    19061909                                         dz_stretch_factor_array,              &   
    19071910                                         dz_stretch_level_end,                 &
     
    19111914    REAL(dp), DIMENSION(:), INTENT(INOUT) ::  dz_stretch_factor_array
    19121915    REAL(dp), DIMENSION(:), INTENT(IN)    ::  dz_stretch_level_end, dz_stretch_level_start
    1913     REAL(dp)                              ::  dz_stretch_factor
    19141916 
    19151917    INTEGER ::  iterations  !< number of iterations until stretch_factor_lower/upper_limit is reached 
     
    41174119    END SUBROUTINE get_soil_layer_thickness
    41184120
    4119  END MODULE grid
     4121 END MODULE inifor_grid
  • palm/trunk/UTIL/inifor/src/inifor_io.f90

    r3615 r3618  
    2626! -----------------
    2727! $Id$
     28! Prefixed all INIFOR modules with inifor_
     29!
     30!
     31! 3615 2018-12-10 07:21:03Z raasch
    2832! bugfix: abort replaced by inifor_abort
    2933!
     
    8791!> INIFOR.
    8892!------------------------------------------------------------------------------!
    89  MODULE io
    90 
    91     USE control
    92     USE defs,                                                                  &
     93 MODULE inifor_io
     94
     95    USE inifor_control
     96    USE inifor_defs,                                                           &
    9397        ONLY:  DATE, SNAME, PATH, PI, dp, hp, TO_RADIANS, TO_DEGREES, VERSION
     98    USE inifor_types
     99    USE inifor_util,                                                           &
     100        ONLY:  reverse, str, real_to_str
    94101    USE netcdf
    95     USE types
    96     USE util,                                                                  &
    97         ONLY:  reverse, str, real_to_str
    98102
    99103    IMPLICIT NONE
     
    12221226    END SUBROUTINE check
    12231227
    1224  END MODULE io
     1228 END MODULE inifor_io
  • palm/trunk/UTIL/inifor/src/inifor_transform.f90

    r3615 r3618  
    2626! -----------------
    2727! $Id$
     28! Prefixed all INIFOR modules with inifor_, removed unused variables
     29!
     30!
     31! 3615 2018-12-10 07:21:03Z raasch
    2832! bugfix: abort replaced by inifor_abort
    2933!
     
    7680!> int2lm's utility routines.
    7781!------------------------------------------------------------------------------!
    78  MODULE transform
    79 
    80     USE control
    81     USE defs,                                                                  &
     82 MODULE inifor_transform
     83
     84    USE inifor_control
     85    USE inifor_defs,                                                           &
    8286        ONLY: G, TO_DEGREES, TO_RADIANS, PI, dp
    83     USE types
    84     USE util,                                                                  &       
     87    USE inifor_types
     88    USE inifor_util,                                                           &
    8589        ONLY: real_to_str, str
    8690
     
    622626                                   lamr(i) * TO_DEGREES,                       &
    623627                                   phip * TO_DEGREES,                          &
    624                                    lamp * TO_DEGREES,                          &
    625628                                   gam  * TO_DEGREES) * TO_RADIANS
    626629
     
    11621165!> Compute the geographical latitude of a point given in rotated-pole cordinates
    11631166!------------------------------------------------------------------------------!
    1164     FUNCTION phirot2phi (phirot, rlarot, polphi, pollam, polgam)
     1167    FUNCTION phirot2phi (phirot, rlarot, polphi, polgam)
    11651168   
    11661169       REAL(dp), INTENT (IN) ::  polphi      !< latitude of the rotated north pole
    1167        REAL(dp), INTENT (IN) ::  pollam      !< longitude of the rotated north pole
    11681170       REAL(dp), INTENT (IN) ::  phirot      !< latitude in the rotated system
    11691171       REAL(dp), INTENT (IN) ::  rlarot      !< longitude in the rotated system
     
    13961398    END SUBROUTINE uvrot2uv
    13971399
    1398  END MODULE
    1399 
     1400 END MODULE inifor_transform
     1401
  • palm/trunk/UTIL/inifor/src/inifor_types.f90

    r3557 r3618  
    2626! -----------------
    2727! $Id$
     28! Prefixed all INIFOR modules with inifor_
     29!
     30!
     31! 3557 2018-11-22 16:01:22Z eckhard
    2832! Updated documentation
    2933!
     
    6165!> The types module provides derived data types used in INIFOR.
    6266!------------------------------------------------------------------------------!
    63  MODULE types
     67 MODULE inifor_types
    6468 
    65  USE defs,                                                                     &
     69 USE inifor_defs,                                                              &
    6670    ONLY:  dp, DATE, PATH, SNAME, LNAME
    6771 USE netcdf,                                                                   &
     
    253257 END TYPE container
    254258
    255  END MODULE types
    256 
     259 END MODULE inifor_types
     260
  • palm/trunk/UTIL/inifor/src/inifor_util.f90

    r3557 r3618  
    2626! -----------------
    2727! $Id$
     28! Prefixed all INIFOR modules with inifor_
     29!
     30!
     31! 3557 2018-11-22 16:01:22Z eckhard
    2832! Updated documentation
    2933!
     
    5458!> The util module provides miscellaneous utility routines for INIFOR.
    5559!------------------------------------------------------------------------------!
    56  MODULE util
    57 
     60 MODULE inifor_util
     61
     62    USE inifor_defs,                                                           &
     63        ONLY :  dp, PI, DATE, SNAME
     64    USE inifor_types,                                                          &
     65        ONLY :  grid_definition
    5866    USE, INTRINSIC :: ISO_C_BINDING,                                           &
    5967        ONLY :  C_CHAR, C_INT, C_PTR, C_SIZE_T
    60     USE defs,                                                                  &
    61         ONLY :  dp, PI, DATE, SNAME
    62     USE types,                                                                 &
    63         ONLY :  grid_definition
    6468
    6569    IMPLICIT NONE
     
    415419    END SUBROUTINE
    416420
    417  END MODULE
    418 
     421 END MODULE inifor_util
     422
Note: See TracChangeset for help on using the changeset viewer.