Ignore:
Timestamp:
Mar 20, 2018 1:00:05 PM (6 years ago)
Author:
knoop
Message:

Added gust module interface calls to restart data modules

File:
1 edited

Legend:

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

    r2821 r2912  
    2424! Former revisions:
    2525! -----------------
    26 !
     26! $Id$
    2727! Initial interface definition
    2828!
     
    6767       gust_data_output_3d, &
    6868       gust_statistics, &
    69        gust_read_restart_data, &
    70        gust_write_restart_data
     69       gust_rrd_global, &
     70       gust_wrd_global, &
     71       gust_rrd_local, &
     72       gust_wrd_local
    7173!
    7274!-- Public parameters, constants and initial values
     
    132134    END INTERFACE gust_statistics
    133135
    134     INTERFACE gust_read_restart_data
    135        MODULE PROCEDURE gust_read_restart_data
    136     END INTERFACE gust_read_restart_data
    137 
    138     INTERFACE gust_write_restart_data
    139        MODULE PROCEDURE gust_write_restart_data
    140     END INTERFACE gust_write_restart_data
     136    INTERFACE gust_rrd_global
     137       MODULE PROCEDURE gust_rrd_global
     138    END INTERFACE gust_rrd_global
     139
     140    INTERFACE gust_wrd_global
     141       MODULE PROCEDURE gust_wrd_global
     142    END INTERFACE gust_wrd_global
     143
     144    INTERFACE gust_rrd_local
     145       MODULE PROCEDURE gust_rrd_local
     146    END INTERFACE gust_rrd_local
     147
     148    INTERFACE gust_wrd_local
     149       MODULE PROCEDURE gust_wrd_local
     150    END INTERFACE gust_wrd_local
    141151
    142152 CONTAINS
     
    447457!> This routine reads the respective restart data for the gust module.
    448458!------------------------------------------------------------------------------!
    449     SUBROUTINE gust_read_restart_data
    450 
    451 
    452        IMPLICIT NONE
    453 
    454 
    455     END SUBROUTINE gust_read_restart_data
     459    SUBROUTINE gust_rrd_global( found )
     460
     461
     462       USE control_parameters,                                                 &
     463           ONLY: length, restart_string
     464
     465
     466       IMPLICIT NONE
     467
     468       LOGICAL, INTENT(OUT)  ::  found
     469
     470
     471       found = .TRUE.
     472
     473
     474       SELECT CASE ( restart_string(1:length) )
     475
     476          CASE ( 'global_paramter' )
     477!             READ ( 13 )  global_parameter
     478
     479          CASE DEFAULT
     480
     481             found = .FALSE.
     482
     483       END SELECT
     484
     485
     486    END SUBROUTINE gust_rrd_global
     487
     488
     489!------------------------------------------------------------------------------!
     490! Description:
     491! ------------
     492!> This routine reads the respective restart data for the gust module.
     493!------------------------------------------------------------------------------!
     494    SUBROUTINE gust_rrd_local( i, k, nxlf, nxlc, nxl_on_file, nxrf, nxrc,      &
     495                               nxr_on_file, nynf, nync, nyn_on_file, nysf,     &
     496                               nysc, nys_on_file, tmp_2d, tmp_3d, found )
     497
     498
     499       USE control_parameters
     500
     501       USE indices
     502
     503       USE kinds
     504
     505       USE pegrid
     506
     507
     508       IMPLICIT NONE
     509
     510       INTEGER(iwp) ::  i               !<
     511       INTEGER(iwp) ::  k               !<
     512       INTEGER(iwp) ::  nxlc            !<
     513       INTEGER(iwp) ::  nxlf            !<
     514       INTEGER(iwp) ::  nxl_on_file     !<
     515       INTEGER(iwp) ::  nxrc            !<
     516       INTEGER(iwp) ::  nxrf            !<
     517       INTEGER(iwp) ::  nxr_on_file     !<
     518       INTEGER(iwp) ::  nync            !<
     519       INTEGER(iwp) ::  nynf            !<
     520       INTEGER(iwp) ::  nyn_on_file     !<
     521       INTEGER(iwp) ::  nysc            !<
     522       INTEGER(iwp) ::  nysf            !<
     523       INTEGER(iwp) ::  nys_on_file     !<
     524
     525       LOGICAL, INTENT(OUT)  ::  found
     526
     527       REAL(wp), DIMENSION(nys_on_file-nbgp:nyn_on_file+nbgp,nxl_on_file-nbgp:nxr_on_file+nbgp) :: tmp_2d   !<
     528       REAL(wp), DIMENSION(nzb:nzt+1,nys_on_file-nbgp:nyn_on_file+nbgp,nxl_on_file-nbgp:nxr_on_file+nbgp) :: tmp_3d   !<
     529
     530!
     531!-- Here the reading of user-defined restart data follows:
     532!-- Sample for user-defined output
     533
     534
     535       found = .TRUE.
     536
     537
     538       SELECT CASE ( restart_string(1:length) )
     539
     540          CASE ( 'u2_av' )
     541!             IF ( .NOT. ALLOCATED( u2_av ) ) THEN
     542!                  ALLOCATE( u2_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
     543!             ENDIF
     544!             IF ( k == 1 )  READ ( 13 )  tmp_3d
     545!                u2_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =         &
     546!                   tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
     547!
     548          CASE DEFAULT
     549
     550             found = .FALSE.
     551
     552          END SELECT
     553
     554
     555    END SUBROUTINE gust_rrd_local
    456556
    457557
     
    461561!> This routine writes the respective restart data for the gust module.
    462562!------------------------------------------------------------------------------!
    463     SUBROUTINE gust_write_restart_data
    464 
    465 
    466        IMPLICIT NONE
    467 
    468 
    469     END SUBROUTINE gust_write_restart_data
     563    SUBROUTINE gust_wrd_global
     564
     565
     566       IMPLICIT NONE
     567
     568! needs preceeding allocation if array
     569!       CALL wrd_write_string( 'global_parameter' )
     570!       WRITE ( 14 )  global_parameter
     571
     572!       IF ( ALLOCATED( inflow_damping_factor ) )  THEN
     573!          CALL wrd_write_string( 'inflow_damping_factor' )
     574!          WRITE ( 14 )  inflow_damping_factor
     575!       ENDIF
     576
     577
     578    END SUBROUTINE gust_wrd_global
     579
     580
     581!------------------------------------------------------------------------------!
     582! Description:
     583! ------------
     584!> This routine writes the respective restart data for the gust module.
     585!------------------------------------------------------------------------------!
     586    SUBROUTINE gust_wrd_local
     587
     588
     589       IMPLICIT NONE
     590
     591
     592! needs preceeding allocation because sould be array
     593!          IF ( ALLOCATED( u2_av ) )  THEN
     594!             CALL wrd_write_string( 'u2_av' )
     595!             WRITE ( 14 )  u2_av
     596!          ENDIF
     597
     598
     599    END SUBROUTINE gust_wrd_local
    470600
    471601
Note: See TracChangeset for help on using the changeset viewer.