source: palm/trunk/SOURCE/uv_exposure_model_mod.f90 @ 3241

Last change on this file since 3241 was 3241, checked in by raasch, 6 years ago

various changes to avoid compiler warnings (mainly removal of unused variables)

  • Property svn:keywords set to Id
File size: 31.2 KB
Line 
1!> @file uv_exposure_model_mod.f90
2!------------------------------------------------------------------------------!
3! This file is part of the PALM model system.
4!
5! PALM is free software: you can redistribute it and/or modify it under the
6! terms of the GNU General Public License as published by the Free Software
7! Foundation, either version 3 of the License, or (at your option) any later
8! version.
9!
10! PALM is distributed in the hope that it will be useful, but WITHOUT ANY
11! WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR
12! A PARTICULAR PURPOSE.  See the GNU General Public License for more details.
13!
14! You should have received a copy of the GNU General Public License along with
15! PALM. If not, see <http://www.gnu.org/licenses/>.
16!
17! Copyright 2017-2018 Leibniz Universitaet Hannover
18!------------------------------------------------------------------------------!
19!
20! Current revisions:
21! -----------------
22!
23!
24! Former revisions:
25! -----------------
26! $Id: uv_exposure_model_mod.f90 3241 2018-09-12 15:02:00Z raasch $
27! unused variables removed
28!
29! 3014 2018-05-09 08:42:38Z maronga
30! Bugfix: domain bounds of local_pf corrected
31!
32! 3004 2018-04-27 12:33:25Z Giersch
33! Further allocation checks implemented (averaged data will be assigned to fill
34! values if no allocation happened so far)
35!
36! 2932 2018-03-26 09:39:22Z maronga
37! renamed uvexposure_par to biometeorology_parameters
38!
39! 2894 2018-03-15 09:17:58Z Giersch
40! Routine for skipping global restart data has been removed, uvem_last_actions
41! has been renamed to uvem_wrd_global and uvem_read_restart_data has been
42! renamed to uvem_rrd_global, variable named found has been introduced for
43! checking if restart data was found, reading of restart strings has been moved
44! completely to read_restart_data_mod, marker *** end new module *** has been
45! removed, strings and their respective lengths are written out and read now
46! in case of restart runs to get rid of prescribed character lengths, CASE
47! DEFAULT was added if restart data is read
48!
49! 2848 2018-03-05 10:11:18Z Giersch
50! Initial revision
51!
52!
53!
54! Authors:
55! --------
56! @author Michael Schrempf
57!
58!
59! Description:
60! ------------
61!> Calculation of vitamin-D weighted UV exposure
62!>
63!>
64!> @todo uv_vitd3dose-->new output type necessary (cumulative)
65!> @todo consider upwelling radiation
66!>
67!> @note <Enter notes on the module>
68!>
69!> @bug  <Enter known bugs here>
70!------------------------------------------------------------------------------!
71 MODULE uv_exposure_model_mod
72 
73
74    USE kinds
75
76!
77!-- Load required variables from existing modules
78!-- USE modulename,                                                            &
79!--     ONLY: ...
80
81
82    IMPLICIT NONE
83
84
85!
86!-- Declare all global variables within the module (alphabetical order)
87    INTEGER(iwp) ::  ai                      = 0 !< running index
88    INTEGER(iwp) ::  clothing                = 3 !< clothing (0=unclothed, 1=Arms,Hands Face free, 3=Hand, Face free)
89    INTEGER(iwp) ::  consider_obstructions   = 1 !< 0 = unobstructed scenario,
90                                                 !< 1 = scenario where obstrcutions are considered
91    INTEGER(iwp) ::  orientation_angle       = 0 !< orientation of front/face of the human model
92    INTEGER(iwp) ::  saa_in_south            = 1 !< 0 = sun always in south direction, 1 = actual sun position 
93    INTEGER(iwp) ::  obstruction_direct_beam = 0 !< Obstruction information for direct beam
94    INTEGER(iwp) ::  turn_to_sun             = 1 !< 0 = orientation of human as in orientation_angle,
95                                                 !< 1 = human is always orientated towards the sun
96    INTEGER(iwp) ::  zi                      = 0 !< running index
97
98    INTEGER(iwp), DIMENSION(0:44)  ::  obstruction_temp1 = 0 !< temporary obstruction information
99                                                             !< stored with ibset as logical information
100    INTEGER(iwp), DIMENSION(0:359) ::  obstruction_temp2 = 0 !< temporary obstruction information restored values
101                                                             !< from logical information, which where stored by ibset 
102   
103    INTEGER(iwp), DIMENSION(0:35,0:9) ::  obstruction = 0 !< final obstruction information array for all
104                                                          !< hemispherical directions
105   
106    INTEGER(KIND=1), DIMENSION(:,:,:), ALLOCATABLE ::  obstruction_lookup_table !< lookup table of obstruction
107                                                                                !< information of entire domain
108
109    REAL(wp) ::  diffuse_exposure            = 0.0_wp !< calculated exposure by diffuse radiation
110    REAL(wp) ::  direct_exposure             = 0.0_wp !< calculated exposure by direct beam   
111    REAL(wp) ::  projection_area_direct_beam = 0.0_wp !< projection area for  by direct beam
112    REAL(wp) ::  saa                         = 180.0_wp !< solar azimuth angle
113    REAL(wp) ::  startpos_human              = 0.0_wp !< start position in azimuth direction for the
114                                                      !< interpolation of the projection area             
115    REAL(wp) ::  startpos_saa_float          = 0.0_wp !< start position in azimuth direction for the
116                                                      !< interpolation of the radiance field             
117    REAL(wp) ::  sza                         = 20.0_wp !< solar zenith angle
118    REAL(wp) ::  xfactor                     = 0.0_wp !< relative x-position used for interpolation
119    REAL(wp) ::  yfactor                     = 0.0_wp !< relative y-position used for interpolation
120   
121    REAL(wp), DIMENSION(0:2)  ::  irradiance  = 0.0_wp !< iradiance values extracted from irradiance lookup table
122   
123    REAL(wp), DIMENSION(0:2,0:90) ::  irradiance_lookup_table = 0.0_wp !< irradiance lookup table contains values
124                                                                       !< for direct, diffuse and global component
125    REAL(wp), DIMENSION(0:35,0:9) ::  integration_array            = 0.0_wp
126    REAL(wp), DIMENSION(0:35,0:9) ::  projection_area              = 0.0_wp
127    REAL(wp), DIMENSION(0:35,0:9) ::  projection_area_lookup_table = 0.0_wp
128    REAL(wp), DIMENSION(0:71,0:9) ::  projection_area_temp         = 0.0_wp
129    REAL(wp), DIMENSION(0:35,0:9) ::  radiance_array               = 0.0_wp
130    REAL(wp), DIMENSION(0:71,0:9) ::  radiance_array_temp          = 0.0_wp
131    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  vitd3_exposure
132    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  vitd3_exposure_av
133
134    REAL(wp), DIMENSION(0:35,0:9,0:90) ::  radiance_lookup_table = 0.0_wp
135
136
137    SAVE
138
139    PRIVATE
140
141   
142!
143!-- Add INTERFACES that must be available to other modules (alphabetical order)
144    PUBLIC uvem_3d_data_averaging, uvem_calc_exposure, uvem_check_data_output, &
145           uvem_data_output_2d, uvem_define_netcdf_grid, uvem_init,            &
146           uvem_init_arrays, uvem_parin
147
148!
149!-- Add VARIABLES that must be available to other modules (alphabetical order)
150!     PUBLIC
151
152!
153!-- Add PROGNOSTIC QUANTITIES that must be available to other modules (alphabetical order)
154!-- PUBLIC ...
155
156
157!
158!-- Default procedures for all new modules (not all are necessarily required,
159!-- alphabetical order is not essential)
160
161!
162!-- PALM interfaces:
163!-- Data output checks for 2D/3D data to be done in check_parameters
164    INTERFACE uvem_check_data_output
165       MODULE PROCEDURE uvem_check_data_output
166    END INTERFACE uvem_check_data_output
167   
168! !
169! !-- Data output checks for profile data to be done in check_parameters
170!     INTERFACE uvem_check_data_output_pr
171!        MODULE PROCEDURE uvem_check_data_output_pr
172!     END INTERFACE uvem_check_data_output_pr
173!     
174! !
175! !-- Input parameter checks to be done in check_parameters
176!     INTERFACE uvem_check_parameters
177!        MODULE PROCEDURE uvem_check_parameters
178!     END INTERFACE uvem_check_parameters
179!
180!
181!-- Averaging of 3D data for output
182    INTERFACE uvem_3d_data_averaging
183       MODULE PROCEDURE uvem_3d_data_averaging
184    END INTERFACE uvem_3d_data_averaging
185!
186! !
187!-- Data output of 2D quantities
188    INTERFACE uvem_data_output_2d
189       MODULE PROCEDURE uvem_data_output_2d
190    END INTERFACE uvem_data_output_2d
191!
192! !
193! !-- Data output of 3D data
194!     INTERFACE uvem_data_output_3d
195!        MODULE PROCEDURE uvem_data_output_3d
196!     END INTERFACE uvem_data_output_3d
197!
198! !
199! !-- Definition of data output quantities
200    INTERFACE uvem_define_netcdf_grid
201       MODULE PROCEDURE uvem_define_netcdf_grid
202    END INTERFACE uvem_define_netcdf_grid
203!
204! !
205! !-- Output of information to the header file
206!     INTERFACE uvem_header
207!        MODULE PROCEDURE uvem_header
208!     END INTERFACE uvem_header
209 
210!
211!-- Initialization actions 
212    INTERFACE uvem_init
213       MODULE PROCEDURE uvem_init
214    END INTERFACE uvem_init
215 
216!
217!-- Initialization of arrays
218    INTERFACE uvem_init_arrays
219       MODULE PROCEDURE uvem_init_arrays
220    END INTERFACE uvem_init_arrays
221!
222! !
223! !-- Writing of binary output for restart runs  !!! renaming?!
224!     INTERFACE uvem_wrd_global
225!        MODULE PROCEDURE uvem_wrd_global
226!     END INTERFACE uvem_wrd_global
227!     
228!
229!-- Reading of NAMELIST parameters
230    INTERFACE uvem_parin
231       MODULE PROCEDURE uvem_parin
232    END INTERFACE uvem_parin
233!
234! !
235! !-- Reading of parameters for restart runs
236!     INTERFACE uvem_rrd_global
237!        MODULE PROCEDURE uvem_rrd_global
238!     END INTERFACE uvem_rrd_global
239!
240! !
241! !-- Swapping of time levels (required for prognostic variables)
242!     INTERFACE uvem_swap_timelevel
243!        MODULE PROCEDURE uvem_swap_timelevel
244!     END INTERFACE uvem_swap_timelevel
245!
246! !
247! !-- New module-specific procedure(s) (alphabetical order):
248!     INTERFACE uvem_newprocedure
249!        MODULE PROCEDURE uvem_newprocedure
250!     END INTERFACE uvem_newprocedure
251
252 CONTAINS
253
254!------------------------------------------------------------------------------!
255! Description:
256! ------------
257!> Check data output for new module.
258!------------------------------------------------------------------------------!
259 SUBROUTINE uvem_check_data_output( var, unit, i, ilen, k )
260 
261    USE control_parameters,                                                    &
262        ONLY:  data_output, message_string, uv_exposure
263
264    IMPLICIT NONE
265
266    CHARACTER (LEN=*) ::  unit     !< string for unit of output quantity
267    CHARACTER (LEN=*) ::  var      !< string for output quantity
268
269    INTEGER(iwp) ::  i      !<
270    INTEGER(iwp) ::  ilen   !<   
271    INTEGER(iwp) ::  k      !<
272
273    SELECT CASE ( TRIM( var ) )
274
275
276       CASE ( 'uvem_vitd3*' )
277          IF (  .NOT.  uv_exposure )  THEN
278             message_string = 'output of "' // TRIM( var ) // '" requi' //  &
279                      'res a namelist &uvexposure_par'
280             CALL message( 'uvem_check_data_output', 'UV0001', 1, 2, 0, 6, 0 )
281          ENDIF
282          IF ( k == 0  .OR.  data_output(i)(ilen-2:ilen) /= '_xy' )  THEN
283             message_string = 'illegal value for data_output: "' //            &
284                              TRIM( var ) // '" & only 2d-horizontal ' //      &
285                              'cross sections are allowed for this value'
286             CALL message( 'check_parameters', 'PA0111', 1, 2, 0, 6, 0 )
287          ENDIF
288          unit = 'IU/s'
289
290       CASE ( 'uvem_vitd3dose*' )
291          IF (  .NOT.  uv_exposure )  THEN
292             message_string = 'output of "' // TRIM( var ) // '" requi' //  &
293                      'res  a namelist &uvexposure_par'
294             CALL message( 'uvem_check_data_output', 'UV0001', 1, 2, 0, 6, 0 )
295          ENDIF
296          IF ( k == 0  .OR.  data_output(i)(ilen-2:ilen) /= '_xy' )  THEN
297             message_string = 'illegal value for data_output: "' //            &
298                              TRIM( var ) // '" & only 2d-horizontal ' //      &
299                              'cross sections are allowed for this value'
300             CALL message( 'check_parameters', 'PA0111', 1, 2, 0, 6, 0 )
301          ENDIF
302          unit = 'IU/av-h'
303             
304       CASE DEFAULT
305          unit = 'illegal'
306
307    END SELECT
308
309 END SUBROUTINE uvem_check_data_output
310
311
312!-----------------------------------------------------------------------------!
313!
314! Description:
315! ------------
316!> Subroutine defining 2D output variables
317!-----------------------------------------------------------------------------!
318 SUBROUTINE uvem_data_output_2d( av, variable, found, grid, local_pf, two_d,   &
319                                 nzb_do, nzt_do )
320 
321    USE indices
322
323    USE kinds
324
325
326    IMPLICIT NONE
327
328    CHARACTER (LEN=*) ::  grid     !<
329    CHARACTER (LEN=*) ::  variable !<
330
331    INTEGER(iwp) ::  av      !<
332    INTEGER(iwp) ::  i       !< running index
333    INTEGER(iwp) ::  j       !< running index
334    INTEGER(iwp) ::  nzb_do  !<
335    INTEGER(iwp) ::  nzt_do  !<
336
337    LOGICAL      ::  found !<
338    LOGICAL      ::  two_d !< flag parameter that indicates 2D variables (horizontal cross sections)
339
340    REAL(wp) ::  fill_value = -999.0_wp    !< value for the _FillValue attribute
341
342    REAL(wp), DIMENSION(nxl:nxr,nys:nyn,nzb_do:nzt_do) ::  local_pf !<
343
344
345    found = .TRUE.
346
347    SELECT CASE ( TRIM( variable ) )
348!
349!--    Before data is transfered to local_pf, transfer is it 2D dummy variable and exchange ghost points therein.
350!--    However, at this point this is only required for instantaneous arrays, time-averaged quantities are already exchanged.
351       CASE ( 'uvem_vitd3*_xy' )        ! 2d-array
352          IF ( av == 0 )  THEN
353             DO  i = nxl, nxr
354                DO  j = nys, nyn
355                   local_pf(i,j,nzb+1) = vitd3_exposure(j,i)
356                ENDDO
357             ENDDO
358          ENDIF
359
360          two_d = .TRUE.
361          grid = 'zu1'
362
363       CASE ( 'uvem_vitd3dose*_xy' )        ! 2d-array
364          IF ( .NOT. ALLOCATED( vitd3_exposure_av ) ) THEN
365             ALLOCATE( vitd3_exposure_av(nysg:nyng,nxlg:nxrg) )
366             vitd3_exposure_av = REAL( fill_value, KIND = wp )
367          ENDIF
368          IF ( av == 1 )  THEN
369             DO  i = nxl, nxr
370                DO  j = nys, nyn
371                   local_pf(i,j,nzb+1) = vitd3_exposure_av(j,i)
372                ENDDO
373             ENDDO
374          ENDIF
375
376          two_d = .TRUE.
377          grid = 'zu1'
378
379       CASE DEFAULT
380          found = .FALSE.
381          grid  = 'none'
382
383    END SELECT
384 
385 END SUBROUTINE uvem_data_output_2d
386
387
388!------------------------------------------------------------------------------!
389!
390! Description:
391! ------------
392!> Subroutine defining appropriate grid for netcdf variables.
393!> It is called out from subroutine netcdf.
394!------------------------------------------------------------------------------!
395 SUBROUTINE uvem_define_netcdf_grid( var, found, grid_x, grid_y, grid_z )
396   
397    IMPLICIT NONE
398
399    CHARACTER (LEN=*), INTENT(IN)  ::  var         !<
400    CHARACTER (LEN=*), INTENT(OUT) ::  grid_x      !<
401    CHARACTER (LEN=*), INTENT(OUT) ::  grid_y      !<
402    CHARACTER (LEN=*), INTENT(OUT) ::  grid_z      !<
403
404    LOGICAL, INTENT(OUT)           ::  found       !<
405
406    found  = .TRUE.
407
408!
409!-- Check for the grid
410    SELECT CASE ( TRIM( var ) )
411
412       CASE ( 'uvem_vitd3*_xy', 'uvem_vitd3dose*_xy' )
413          grid_x = 'x'
414          grid_y = 'y'
415          grid_z = 'zu1'
416
417       CASE DEFAULT
418          found  = .FALSE.
419          grid_x = 'none'
420          grid_y = 'none'
421          grid_z = 'none'
422
423    END SELECT
424
425 END SUBROUTINE uvem_define_netcdf_grid
426
427
428!------------------------------------------------------------------------------!
429! Description:
430! ------------
431!> Parin for &uvexposure_par for UV exposure model
432!------------------------------------------------------------------------------!
433 SUBROUTINE uvem_parin
434
435    USE control_parameters,                                                   &
436        ONLY:  uv_exposure
437
438
439    IMPLICIT NONE
440
441    CHARACTER (LEN=80) ::  line  !< dummy string for current line in parameter file
442   
443    NAMELIST /biometeorology_parameters/  clothing
444   
445    line = ' '
446   
447!
448!-- Try to find uv exposure model namelist
449    REWIND ( 11 )
450    line = ' '
451    DO   WHILE ( INDEX( line, '&biometerology_parameters' ) == 0 )
452       READ ( 11, '(A)', END=10 )  line
453    ENDDO
454    BACKSPACE ( 11 )
455
456!
457!-- Read user-defined namelist
458    READ ( 11, biometeorology_parameters )
459
460!
461!-- Set flag that indicates that the uv exposure model is switched on
462    uv_exposure = .TRUE.
463
464
465 10 CONTINUE
466       
467
468 END SUBROUTINE uvem_parin
469
470
471!------------------------------------------------------------------------------!
472!
473! Description:
474! ------------
475!> Subroutine for averaging 3D data
476!------------------------------------------------------------------------------!
477 SUBROUTINE uvem_3d_data_averaging( mode, variable )
478 
479
480    USE control_parameters
481
482    USE indices
483
484    USE kinds
485
486    IMPLICIT NONE
487
488    CHARACTER (LEN=*) ::  mode    !<
489    CHARACTER (LEN=*) :: variable !<
490
491    INTEGER(iwp) ::  i       !<
492    INTEGER(iwp) ::  j       !<
493
494    IF ( mode == 'allocate' )  THEN
495
496       SELECT CASE ( TRIM( variable ) )
497
498          CASE ( 'uvem_vitd3dose*' )
499             IF ( .NOT. ALLOCATED( vitd3_exposure_av ) )  THEN
500                ALLOCATE( vitd3_exposure_av(nysg:nyng,nxlg:nxrg) )
501             ENDIF
502             vitd3_exposure_av = 0.0_wp
503
504
505          CASE DEFAULT
506             CONTINUE
507
508       END SELECT
509
510    ELSEIF ( mode == 'sum' )  THEN
511
512       SELECT CASE ( TRIM( variable ) )
513
514          CASE ( 'uvem_vitd3dose*' )
515             IF ( ALLOCATED( vitd3_exposure_av ) ) THEN
516                DO  i = nxlg, nxrg
517                   DO  j = nysg, nyng
518                      vitd3_exposure_av(j,i) = vitd3_exposure_av(j,i) + vitd3_exposure(j,i)
519                   ENDDO
520                ENDDO
521             ENDIF
522
523
524          CASE DEFAULT
525             CONTINUE
526
527       END SELECT
528
529!
530!-- No averaging since we are calculating a dose (only sum is calculated and saved to
531!-- av.nc file)
532!    ELSEIF ( mode == 'average' )  THEN
533
534    ENDIF
535
536 END SUBROUTINE uvem_3d_data_averaging
537
538   
539
540
541!------------------------------------------------------------------------------!
542! Description:
543! ------------
544!> Initialization of the new module
545!------------------------------------------------------------------------------!
546 SUBROUTINE uvem_init
547   
548
549    USE control_parameters,                                                   &
550        ONLY:  initializing_actions
551
552    IMPLICIT NONE
553
554!
555!-- Actions for initial runs
556    IF ( TRIM( initializing_actions ) /= 'read_restart_data' )  THEN
557       OPEN(90, STATUS='old',FILE=&
558       'RADIANCE', FORM='UNFORMATTED')
559       READ(90) radiance_lookup_table
560       CLOSE(90)
561       OPEN(90, STATUS='old',FILE=&
562       'IRRADIANCE', FORM='UNFORMATTED')
563       READ(90) irradiance_lookup_table
564       CLOSE(90)
565     
566      !________________________LOAD Obstruction information _______________________________
567       IF ( consider_obstructions == 1 )  THEN
568          OPEN(90, STATUS='old',FILE=&
569          'OBSTRUCTION', FORM='UNFORMATTED')
570          READ(90) obstruction_lookup_table
571          CLOSE(90) 
572      ELSEIF( consider_obstructions == 0 ) THEN
573          obstruction(:,:) = 1
574      ENDIF
575
576      !________________________LOAD integration_array ________________________________________________________________________
577      OPEN(90, STATUS='old',FILE=&
578      'SOLIDANGLE', FORM='UNFORMATTED')
579      READ(90) integration_array
580      CLOSE(90)
581
582      IF (clothing==1) THEN
583          OPEN(90, STATUS='old',FILE='HUMAN', FORM='UNFORMATTED')
584      ENDIF
585      READ(90) projection_area_lookup_table
586      CLOSE(90)
587
588!
589!-- Actions for restart runs
590    ELSE
591! ....
592
593    ENDIF
594
595 END SUBROUTINE uvem_init
596
597
598!-----------------------------------------------------------------------------!
599! Description:
600! ------------
601!> Allocate new module arrays and define pointers if required
602!-----------------------------------------------------------------------------!
603 SUBROUTINE uvem_init_arrays
604   
605    USE indices,                                                              &
606        ONLY:  nxlg, nxrg, nyng, nysg
607
608
609    IMPLICIT NONE
610
611!
612!-- Allocate arrays
613    ALLOCATE ( vitd3_exposure(nysg:nyng,nxlg:nxrg) )
614    ALLOCATE ( vitd3_exposure_av(nysg:nyng,nxlg:nxrg) )
615    ALLOCATE ( obstruction_lookup_table(nxlg:nxrg,nysg:nyng,0:44) )
616
617!
618!-- Initialize arrays
619    vitd3_exposure = 0.0_wp
620    vitd3_exposure_av = 0.0_wp
621    obstruction_lookup_table = 0
622
623
624 END SUBROUTINE uvem_init_arrays
625
626!------------------------------------------------------------------------------!
627! Description:
628! ------------
629!> Module-specific routine for new module
630!------------------------------------------------------------------------------!
631 SUBROUTINE uvem_solar_position 
632
633    USE constants,                                                             &
634       ONLY:  pi
635   
636    USE date_and_time_mod,                                                     &
637       ONLY:  calc_date_and_time, day_of_year, time_utc 
638   
639    USE control_parameters,                                                    &
640       ONLY:  latitude, longitude   
641
642    IMPLICIT NONE
643   
644   
645    REAL(wp) ::  alpha       = 0.0_wp   !< solar azimuth angle in radiant       
646    REAL(wp) ::  declination = 0.0_wp   !< declination
647    REAL(wp) ::  dtor        = 0.0_wp   !< factor to convert degree to radiant
648    REAL(wp) ::  js          = 0.0_wp   !< parameter for solar position calculation
649    REAL(wp) ::  lat         = 52.39_wp !< latitude
650    REAL(wp) ::  lon         = 9.7_wp   !< longitude       
651    REAL(wp) ::  thetar      = 0.0_wp   !< angle for solar zenith angle calculation
652    REAL(wp) ::  thetasr     = 0.0_wp   !< angle for solar azimuth angle calculation   
653    REAL(wp) ::  zgl         = 0.0_wp   !< calculated exposure by direct beam   
654    REAL(wp) ::  woz         = 0.0_wp   !< calculated exposure by diffuse radiation
655    REAL(wp) ::  wsp         = 0.0_wp   !< calculated exposure by direct beam   
656   
657
658    CALL calc_date_and_time
659       
660    dtor = pi / 180.0_wp
661    lat = latitude
662    lon = longitude
663!
664!-- calculation of js :
665    js=  72.0_wp * ( day_of_year + ( time_utc / 86400.0_wp ) ) / 73.0_wp 
666!
667!-- calculation of equation of time (zgl):
668    zgl = 0.0066_wp + 7.3525_wp * cos( ( js + 85.9_wp ) * dtor ) + 9.9359_wp *                     &
669    cos( ( 2.0_wp * js + 108.9_wp ) * dtor ) + 0.3387_wp * cos( ( 3 * js + 105.2_wp ) * dtor )
670!
671!-- calculation of apparent solar time woz:
672    woz = ( ( time_utc / 3600.0_wp ) - ( 4.0_wp * ( 15.0_wp - lon ) ) / 60.0_wp ) + ( zgl / 60.0_wp )
673!
674!-- calculation of hour angle (wsp):
675    wsp = ( woz - 12.0_wp ) * 15.0_wp
676!
677!-- calculation of declination:
678    declination = 0.3948_wp - 23.2559_wp * cos( ( js + 9.1_wp ) * dtor ) -                         &
679    0.3915_wp * cos( ( 2.0_wp * js + 5.4_wp ) * dtor ) - 0.1764_wp * cos( ( 3.0_wp * js + 26.0_wp ) * dtor )
680!
681!-- calculation of solar zenith angle
682    thetar  = acos( sin( lat * dtor) * sin( declination * dtor ) + cos( wsp * dtor ) *             &
683    cos( lat * dtor ) * cos( declination * dtor ) )
684    thetasr = asin( sin( lat * dtor) * sin( declination * dtor ) + cos( wsp * dtor ) *             & 
685    cos( lat * dtor ) * cos( declination * dtor ) )
686    sza = thetar / dtor
687!
688!-- calculation of solar azimuth angle
689    IF (woz .LE. 12.0_wp) alpha = pi - acos( sin(thetasr) * sin(lat * dtor) -                           & 
690    sin( declination * dtor ) / ( cos(thetasr) * cos( lat * dtor ) ) )   
691    IF (woz .GT. 12.0_wp) alpha = pi + acos( sin(thetasr) * sin(lat * dtor) -                           &
692    sin( declination * dtor ) / ( cos(thetasr) * cos( lat * dtor ) ) )   
693    saa = alpha / dtor
694
695 END SUBROUTINE uvem_solar_position
696
697
698!------------------------------------------------------------------------------!
699! Description:
700! ------------
701!> Module-specific routine for new module
702!------------------------------------------------------------------------------!
703 SUBROUTINE uvem_calc_exposure
704   
705    USE constants,                                                             &
706        ONLY:  pi
707
708    USE indices,                                                               &
709        ONLY:  nxlg, nxrg, nyng, nysg
710   
711   
712    IMPLICIT NONE   
713   
714    INTEGER(iwp) ::  i   !< running index
715    INTEGER(iwp) ::  j   !< running index
716
717
718    CALL uvem_solar_position
719     
720    IF (sza .GE. 90) THEN
721       vitd3_exposure(:,:) = 0.0_wp
722    ELSE
723       
724!       
725!--    rotate 3D-Model human to desired direction  -----------------------------
726       projection_area_temp( 0:35,:) = projection_area_lookup_table
727       projection_area_temp(36:71,:) = projection_area_lookup_table               
728       IF ( Turn_to_Sun .EQ. 0 )  startpos_human = orientation_angle / 10.0_wp
729       IF ( Turn_to_Sun .EQ. 1 )  startpos_human = startpos_saa_float       
730       DO  ai = 0, 35
731           xfactor = ( startpos_human ) - INT( startpos_human )
732          DO  zi = 0, 9
733              projection_area(ai,zi) = ( projection_area_temp( ai +     INT( startpos_human ), zi) * &
734                                       (1.0_wp - xfactor ) ) &
735                                      +( projection_area_temp( ai + 1 + INT( startpos_human ), zi) * &
736                                        xfactor)
737          ENDDO
738       ENDDO
739!     
740!--    calculate Projectionarea for direct beam -----------------------------'
741       projection_area_temp( 0:35,:) = projection_area
742       projection_area_temp(36:71,:) = projection_area
743       yfactor = ( sza / 10.0_wp ) - INT( sza / 10.0_wp )
744       xfactor = ( startpos_saa_float ) - INT( startpos_saa_float )
745       projection_area_direct_beam = ( projection_area_temp( INT(startpos_saa_float)    ,INT( sza / 10.0_wp ) ) * &
746                                     ( 1.0_wp - xfactor ) * ( 1.0_wp - yfactor ) ) + &
747                                     ( projection_area_temp( INT(startpos_saa_float) + 1,INT(sza/10.0_wp))  *&
748                                     (    xfactor ) * ( 1.0_wp - yfactor ) ) + &
749                                     ( projection_area_temp( INT(startpos_saa_float)    ,INT(sza/10.0_wp)+1)*&
750                                     ( 1.0_wp - xfactor ) * (   yfactor ) ) + &
751                                     ( projection_area_temp( INT(startpos_saa_float) + 1,INT(sza/10.0_wp)+1)*&
752                                     (    xfactor ) * (   yfactor ) )
753                 
754             
755!           
756!--    interpolate to accurate Solar Zenith Angle  ------------------         
757       DO  ai = 0, 35
758          xfactor = (sza)-INT(sza)
759          DO  zi = 0, 9
760              radiance_array(ai,zi) = ( radiance_lookup_table(ai, zi, INT(sza) ) * ( 1.0_wp - xfactor) ) +&
761              ( radiance_lookup_table(ai,zi,INT(sza) + 1) * xfactor )
762          ENDDO
763       ENDDO
764       Do  ai = 0, 2           
765           irradiance(ai) = ( irradiance_lookup_table(ai, INT(sza) ) * ( 1.0_wp - xfactor)) + &
766           (irradiance_lookup_table(ai, INT(sza) + 1) * xfactor )
767       ENDDO   
768!         
769!--    interpolate to accurate Solar Azimuth Angle ------------------
770       IF ( saa_in_south .EQ. 0 )  THEN
771          startpos_saa_float = 180.0_wp / 10.0_wp
772       ELSE
773          startpos_saa_float = saa / 10.0_wp
774       ENDIF
775       radiance_array_temp( 0:35,:) = radiance_array
776       radiance_array_temp(36:71,:) = radiance_array
777       xfactor = (startpos_saa_float) - INT(startpos_saa_float)
778       DO  ai = 0, 35
779          DO  zi = 0, 9
780             radiance_array(ai,zi) = ( radiance_array_temp( ai + INT( startpos_saa_float ), zi ) * &
781                                     (1.0_wp - xfactor)) &
782                                     + ( radiance_array_temp( ai + 1 + INT( startpos_saa_float ), zi ) &
783                                     * xfactor)
784          ENDDO
785       ENDDO 
786
787
788
789                                   
790       DO  i = nxlg, nxrg   
791          DO  j = nysg, nyng
792!           
793!--          extract obstrcution from IBSET-Integer_Array ------------------'
794             IF (consider_obstructions == 1) THEN
795                obstruction_temp1 = obstruction_lookup_table(i,j,:)
796                IF (obstruction_temp1(0) .NE. 9) THEN
797                   DO  zi = 0, 44 
798                      DO  ai = 0, 7 
799                         IF ( btest( obstruction_temp1(zi), ai ) .EQV. .TRUE.) THEN
800                            obstruction_temp2( ( zi * 8 ) + ai ) = 1
801                         ELSE
802                            obstruction_temp2( ( zi * 8 ) + ai ) = 0
803                         ENDIF
804                      ENDDO
805                   ENDDO       
806                   DO  zi = 0, 9                                         
807                      obstruction(:,zi) = obstruction_temp2( zi * 36 :( zi * 36) + 35 )
808                   ENDDO
809                ELSE
810                   obstruction(:,:) = 0
811                ENDIF
812             ENDIF
813!             
814!--          calculated human exposure ------------------' 
815             diffuse_exposure = SUM( radiance_array * projection_area * integration_array * obstruction )     
816         
817             obstruction_direct_beam = obstruction( nint(startpos_saa_float), nint( sza / 10.0_wp ) ) 
818             IF (sza .GE. 89.99_wp) THEN
819                sza = 89.99999_wp
820             ENDIF
821!             
822!--          calculate direct normal irradiance (direct beam) ------------------'
823             direct_exposure = ( irradiance(1) / cos( pi * sza / 180.0_wp ) ) * &
824             projection_area_direct_beam * obstruction_direct_beam 
825               
826             vitd3_exposure(j,i) = ( diffuse_exposure + direct_exposure ) / 1000.0_wp * 70.97_wp 
827             ! unit = international units vitamin D per second             
828          ENDDO
829       ENDDO
830    ENDIF
831
832 END SUBROUTINE uvem_calc_exposure
833
834
835
836
837 
838! ------------------------------------------------------------------------------!
839! Description:
840! ------------
841! > Check parameters routine
842! ------------------------------------------------------------------------------!
843!  SUBROUTINE uvem_check_parameters
844!
845!     USE control_parameters,                                                    &
846!         ONLY:  message_string
847!
848!       
849!     IMPLICIT NONE
850!
851!
852! --    Checks go here (cf. check_parameters.f90).
853!           
854!  END SUBROUTINE uvem_check_parameters
855
856
857 
858! !------------------------------------------------------------------------------!
859! ! Description:
860! ! ------------
861! !> Header output
862! !------------------------------------------------------------------------------!
863!  SUBROUTINE uvem_header ( io )
864!
865!
866!     IMPLICIT NONE
867!
868
869!     INTEGER(iwp), INTENT(IN) ::  io   !< Unit of the output file
870
871! !
872! !-- Header output goes here
873! !-- ...
874!
875!  END SUBROUTINE uvem_header
876
877
878
879! !------------------------------------------------------------------------------!
880! ! Description:
881! ! ------------
882! !> This routine reads the global restart data.
883! !------------------------------------------------------------------------------!
884!  SUBROUTINE uvem_rrd_global
885!
886!
887!     USE control_parameters,                                                    &
888!         ONLY: length, restart_string
889!
890!
891!     IMPLICIT NONE
892!
893!     LOGICAL, INTENT(OUT)  ::  found
894!
895!
896!     found = .TRUE.
897!       
898!       
899!     SELECT CASE ( restart_string(1:length) )
900!
901!       CASE ( 'param1' )
902!          READ ( 13 )  param1
903!
904!        CASE DEFAULT
905!
906!          found = .FALSE.   
907!
908!     END SELECT
909!
910!  END SUBROUTINE uvem_rrd_global 
911   
912
913! !------------------------------------------------------------------------------!
914! ! Description:
915! ! ------------
916! !> This routine writes the global restart data.
917! !------------------------------------------------------------------------------!
918!  SUBROUTINE uvem_wrd_global
919!
920!
921!     IMPLICIT NONE
922!
923!
924!     CALL wrd_write_string( 'param1' )
925!     WRITE ( 14 )  param1         
926!
927!       
928!       
929!  END SUBROUTINE uvem_wrd_global   
930
931
932 END MODULE uv_exposure_model_mod
Note: See TracBrowser for help on using the repository browser.