MODULE ls_forcing_mod !--------------------------------------------------------------------------------! ! This file is part of PALM. ! ! PALM is free software: you can redistribute it and/or modify it under the terms ! of the GNU General Public License as published by the Free Software Foundation, ! either version 3 of the License, or (at your option) any later version. ! ! PALM is distributed in the hope that it will be useful, but WITHOUT ANY ! WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR ! A PARTICULAR PURPOSE. See the GNU General Public License for more details. ! ! You should have received a copy of the GNU General Public License along with ! PALM. If not, see . ! ! Copyright 1997-2012 Leibniz University Hannover !--------------------------------------------------------------------------------! ! ! Current revisions: ! ------------------ ! remove call of user module ! reformatting ! ! Former revisions: ! ----------------- ! $Id: ls_forcing.f90 1249 2013-11-06 10:45:47Z heinze $ ! ! 1241 2013-10-30 11:36:58Z heinze ! Initial revision ! ! Description: ! ------------ ! Calculates large scale forcings (geostrophic wind and subsidence velocity) as ! well as surfaces fluxes dependend on time given in an external file (LSF_DATA). ! Code is based in parts on DALES and UCLA-LES. !--------------------------------------------------------------------------------! PRIVATE PUBLIC init_ls_forcing, ls_forcing_surf, ls_forcing_vert SAVE CONTAINS SUBROUTINE init_ls_forcing USE arrays_3d USE control_parameters USE cpulog USE indices USE interfaces USE pegrid IMPLICIT NONE INTEGER :: finput = 90, ierrn, k, t CHARACTER (100):: chmess CHARACTER(1) :: hash REAL :: r_dummy, fac REAL :: highheight, highug_vert, highvg_vert, highwsubs_vert REAL :: lowheight, lowug_vert, lowvg_vert, lowwsubs_vert ALLOCATE( p_surf(0:nlsf), pt_surf(0:nlsf), q_surf(0:nlsf), & qsws_surf(0:nlsf), shf_surf(0:nlsf), time_vert(0:nlsf), & time_surf(0:nlsf), ug_vert(nzb:nzt+1,0:nlsf), & vg_vert(nzb:nzt+1,0:nlsf), wsubs_vert(nzb:nzt+1,0:nlsf) ) p_surf = 0.0; pt_surf = 0.0; q_surf = 0.0; qsws_surf = 0.0 shf_surf = 0.0; time_vert = 0.0; time_surf = 0.0; ug_vert = 0.0 vg_vert = 0.0; wsubs_vert = 0.0 OPEN ( finput, FILE='LSF_DATA', STATUS='OLD', & FORM='FORMATTED', IOSTAT=ierrn ) IF ( ierrn /= 0 ) THEN message_string = 'file LSF_DATA does not exist' CALL message( 'ls_forcing', 'PA0368', 1, 2, 0, 6, 0 ) ENDIF ierrn = 0 ! !-- First three lines of LSF_DATA contain header READ ( finput, FMT='(a100)', IOSTAT=ierrn ) chmess READ ( finput, FMT='(a100)', IOSTAT=ierrn ) chmess READ ( finput, FMT='(a100)', IOSTAT=ierrn ) chmess IF ( ierrn /= 0 ) THEN message_string = 'errors in file LSF_DATA' CALL message( 'ls_forcing', 'PA0369', 1, 2, 0, 6, 0 ) ENDIF ! !-- Surface values are read in t = 0 ierrn = 0 DO WHILE ( time_surf(t) < end_time ) t = t + 1 READ ( finput, *, IOSTAT = ierrn ) time_surf(t), shf_surf(t), & qsws_surf(t), pt_surf(t), & q_surf(t), p_surf(t) IF ( ierrn < 0 ) THEN WRITE ( message_string, * ) 'No time dependend surface variables ',& 'in&LSF_DATA for end of run found' CALL message( 'ls_forcing', 'PA0370', 1, 2, 0, 6, 0 ) ENDIF ENDDO IF ( time_surf(1) > end_time ) THEN WRITE ( message_string, * ) 'No time dependend surface variables in ',& '&LSF_DATA for end of run found - ', & 'lsf_surf is set to FALSE' CALL message( 'ls_forcing', 'PA0371', 0, 0, 0, 6, 0 ) lsf_surf = .FALSE. ENDIF ! !-- Go to the end of the list with surface variables DO WHILE ( ierrn == 0 ) READ ( finput, *, IOSTAT = ierrn ) r_dummy ENDDO ! !-- Profiles of ug, vg and w_subs are read in (large scale forcing) t = 0 DO WHILE ( time_vert(t) < end_time ) t = t + 1 hash = "#" ierrn = 1 ! not zero ! !-- Search for the next line consisting of "# time", !-- from there onwards the profiles will be read DO WHILE ( .NOT. ( hash == "#" .AND. ierrn == 0 ) ) READ ( finput, *, IOSTAT=ierrn ) hash, time_vert(t) IF ( ierrn < 0 ) THEN WRITE( message_string, * ) 'No time dependend vertical profiles',& ' in&LSF_DATA for end of run found' CALL message( 'ls_forcing', 'PA0372', 1, 2, 0, 6, 0 ) ENDIF ENDDO IF ( t == 1 .AND. time_vert(t) > end_time ) EXIT READ ( finput, *, IOSTAT=ierrn ) lowheight, lowug_vert, lowvg_vert, & lowwsubs_vert IF ( ierrn /= 0 ) THEN message_string = 'errors in file LSF_DATA' CALL message( 'nudging', 'PA0369', 1, 2, 0, 6, 0 ) ENDIF READ ( finput, *, IOSTAT=ierrn ) highheight, highug_vert, highvg_vert, & highwsubs_vert IF ( ierrn /= 0 ) THEN message_string = 'errors in file LSF_DATA' CALL message( 'nudging', 'PA0369', 1, 2, 0, 6, 0 ) ENDIF DO k = nzb, nzt+1 IF ( highheight < zu(k) ) THEN lowheight = highheight lowug_vert = highug_vert lowvg_vert = highvg_vert lowwsubs_vert = highwsubs_vert ierrn = 0 READ ( finput, *, IOSTAT=ierrn ) highheight, highug_vert, & highvg_vert, highwsubs_vert IF ( ierrn /= 0 ) THEN message_string = 'errors in file LSF_DATA' CALL message( 'nudging', 'PA0369', 1, 2, 0, 6, 0 ) ENDIF ENDIF ! !-- Interpolation of prescribed profiles in space fac = (highheight-zu(k))/(highheight - lowheight) ug_vert(k,t) = fac*lowug_vert + (1-fac)*highug_vert vg_vert(k,t) = fac*lowvg_vert + (1-fac)*highvg_vert wsubs_vert(k,t) = fac*lowwsubs_vert + (1-fac)*highwsubs_vert ENDDO ENDDO IF ( time_vert(1) > end_time ) THEN WRITE ( message_string, * ) 'Time dependent large scale profile ',& 'forcing from&LSF_DATA sets in after end of ' ,& 'simulation - lsf_vert is set to FALSE' CALL message( 'ls_forcing', 'PA0373', 0, 0, 0, 6, 0 ) lsf_vert = .FALSE. ENDIF CLOSE( finput ) END SUBROUTINE init_ls_forcing SUBROUTINE ls_forcing_surf ( time ) USE arrays_3d USE control_parameters USE cpulog USE indices USE interfaces USE pegrid IMPLICIT NONE REAL, INTENT(in) :: time REAL :: fac INTEGER :: t ! !-- Interpolation in time of LSF_DATA at the surface t = 1 DO WHILE ( time > time_surf(t) ) t = t + 1 ENDDO IF ( time /= time_surf(t) ) THEN t = t - 1 ENDIF fac = ( time -time_surf(t) ) / ( time_surf(t+1) - time_surf(t) ) shf = shf_surf(t) + fac * ( shf_surf(t+1) - shf_surf(t) ) qsws = qsws_surf(t) + fac * ( qsws_surf(t+1) - qsws_surf(t) ) pt_surface = pt_surf(t) + fac * ( pt_surf(t+1) - pt_surf(t) ) surface_pressure = p_surf(t) + fac * ( p_surf(t+1) - p_surf(t) ) END SUBROUTINE ls_forcing_surf SUBROUTINE ls_forcing_vert ( time ) USE arrays_3d USE control_parameters USE cpulog USE indices USE interfaces USE pegrid IMPLICIT NONE REAL, INTENT(in) :: time REAL :: fac INTEGER :: t ! !-- Interpolation in time of LSF_DATA for ug, vg and w_subs t = 1 DO WHILE ( time > time_vert(t) ) t = t + 1 ENDDO IF ( time /= time_vert(t) ) THEN t = t - 1 ENDIF fac = ( time-time_vert(t) ) / ( time_vert(t+1)-time_vert(t) ) ug = ug_vert(:,t) + fac * ( ug_vert(:,t+1) - ug_vert(:,t) ) vg = vg_vert(:,t) + fac * ( vg_vert(:,t+1) - vg_vert(:,t) ) IF ( large_scale_subsidence ) THEN w_subs = wsubs_vert(:,t) + fac * ( wsubs_vert(:,t+1) - wsubs_vert(:,t) ) ENDIF END SUBROUTINE ls_forcing_vert END MODULE ls_forcing_mod