Ignore:
Timestamp:
Dec 14, 2017 5:12:51 PM (6 years ago)
Author:
kanani
Message:

Merge of branch palm4u into trunk

Location:
palm/trunk
Files:
3 edited

Legend:

Unmodified
Added
Removed
  • palm/trunk

  • palm/trunk/SOURCE

  • palm/trunk/SOURCE/read_3d_binary.f90

    r2644 r2696  
    11!> @file read_3d_binary.f90
    22!------------------------------------------------------------------------------!
    3 ! This file is part of PALM.
     3! This file is part of the PALM model system.
    44!
    55! PALM is free software: you can redistribute it and/or modify it under the
     
    2121! -----------------
    2222!
    23 !
     23! 
    2424! Former revisions:
    2525! -----------------
    2626! $Id$
     27! - kh_av, km_av (TG)
     28! - Implementation of chemistry module (FK)
     29! - Changes from trunk concerning random generator added (MS)
     30!
     31! 2644 2017-11-27 09:27:09Z raasch
    2732! further bugfix for r2636 (wrong datatype used for allocation)
    2833!
     
    144149    USE averaging
    145150
     151#if defined( __chem )
     152    USE chemistry_model_mod,                                                   &
     153        ONLY:  chem_read_restart_data, chem_species, nspec                               
     154#endif
     155
    146156    USE control_parameters,                                                    &
    147         ONLY:  iran, land_surface, message_string, outflow_l, outflow_n,       &
    148                outflow_r, outflow_s, urban_surface
     157        ONLY:  air_chemistry, iran, land_surface, message_string, outflow_l,   &
     158               outflow_n, outflow_r, outflow_s, urban_surface
    149159
    150160    USE cpulog,                                                                &
     
    234244    REAL(wp) ::  rdummy
    235245
    236     REAL(wp), DIMENSION(:,:), ALLOCATABLE     ::  tmp_2d      !< temporary array for storing 2D data
     246    REAL(wp), DIMENSION(:,:),   ALLOCATABLE   ::  tmp_2d      !< temporary array for storing 2D data
    237247    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE   ::  tmp_3d      !< temporary array for storing 3D data
    238248    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE   ::  tmp_3dwul   !<
     
    360370!--    First compare the version numbers
    361371       READ ( 13 )  version_on_file
    362        binary_version = '4.5'
     372       binary_version = '4.6'
    363373       IF ( TRIM( version_on_file ) /= TRIM( binary_version ) )  THEN
    364374          WRITE( message_string, * ) 'version mismatch concerning data ',      &
     
    460470             nync = nynfa(i,k) + offset_ya(i,k)
    461471
    462              write(9,*) "f", nxlf, nxrf, nysf, nynf
    463              write(9,*) "c", nxlc, nxrc, nysc, nync
    464 
    465472
    466473
     
    489496                             tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
    490497
     498                CASE ( 'kh_av' )
     499                   IF ( .NOT. ALLOCATED( kh_av ) )  THEN
     500                      ALLOCATE( kh_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg ))
     501                   ENDIF
     502                   IF ( k == 1 )  READ ( 13 )  tmp_3d
     503                   kh_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) = &
     504                                tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
     505
    491506                CASE ( 'km' )
    492507                   IF ( k == 1 )  READ ( 13 )  tmp_3d
    493508                   km(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) = &
    494509                               tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
     510
     511                CASE ( 'km_av' )
     512                   IF ( .NOT. ALLOCATED( km_av ) )  THEN
     513                      ALLOCATE( km_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg ))
     514                   ENDIF
     515                   IF ( k == 1 )  READ ( 13 )  tmp_3d
     516                   km_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) = &
     517                                tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
    495518
    496519                CASE ( 'lpt_av' )
     
    703726                   IF ( k == 1 )  READ ( 13 )  random_iv
    704727                   IF ( k == 1 )  READ ( 13 )  random_iy
    705                    
     728
    706729                CASE ( 'seq_random_array' )
    707730                   ALLOCATE( tmp_2d_id_random(nys_on_file:nyn_on_file,         &
     
    722745                                       tmp_2d_seq_random(:,nysf:nynf,nxlf:nxrf)
    723746                   DEALLOCATE( tmp_2d_id_random, tmp_2d_seq_random )
     747
    724748                CASE ( 'rho_ocean_av' )
    725749                   IF ( .NOT. ALLOCATED( rho_ocean_av ) )  THEN
     
    10541078
    10551079!
     1080!--    Read urban surface restart data
     1081       IF ( urban_surface )  THEN
     1082          CALL usm_read_restart_data( i, nxlfa, nxl_on_file, nxrfa,            &
     1083                                      nxr_on_file, nynfa, nyn_on_file, nysfa,  &
     1084                                      nys_on_file, offset_xa, offset_ya,       &
     1085                                      overlap_count(i) )
     1086       ENDIF
     1087
     1088!
    10561089!--    Read land surface restart data
    10571090       IF ( land_surface )  THEN
     
    10611094                                      overlap_count(i), tmp_2d )
    10621095
    1063        ENDIF
    1064        
    1065 !
    1066 !--    Read land surface restart data
    1067        IF ( urban_surface )  THEN
    1068           CALL usm_read_restart_data( i, nxlfa, nxl_on_file, nxrfa,            &
    1069                                       nxr_on_file, nynfa, nyn_on_file, nysfa,  &
    1070                                       nys_on_file, offset_xa, offset_ya,       &
    1071                                       overlap_count(i) )
    10721096       ENDIF
    10731097
     
    10831107
    10841108!
     1109!--    Read chemistry restart data
     1110#if defined( __chem )
     1111       IF ( air_chemistry )  THEN
     1112          CALL chem_read_restart_data( i, nxlfa, nxl_on_file, nxrfa,           &
     1113                                       nxr_on_file, nynfa, nyn_on_file,        &
     1114                                       nysfa, nys_on_file, offset_xa,          &
     1115                                       offset_ya, overlap_count(i),            &
     1116                                       tmp_2d, tmp_3d )
     1117       ENDIF
     1118#endif
     1119
     1120!
    10851121!--    Read user-defined restart data
    10861122       CALL user_read_restart_data( i, nxlfa, nxl_on_file, nxrfa, nxr_on_file, &
Note: See TracChangeset for help on using the changeset viewer.