/[MITgcm]/MITgcm/pkg/dic/insol.F
ViewVC logotype

Contents of /MITgcm/pkg/dic/insol.F

Parent Directory Parent Directory | Revision Log Revision Log | View Revision Graph Revision Graph


Revision 1.12 - (show annotations) (download)
Wed Apr 9 22:13:15 2008 UTC (16 years, 2 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint60, checkpoint61, checkpoint62, checkpoint59q, checkpoint59p, checkpoint59r, checkpoint62c, checkpoint62b, checkpoint62a, checkpoint62d, checkpoint61f, checkpoint61g, checkpoint61d, checkpoint61e, checkpoint61b, checkpoint61c, checkpoint61a, checkpoint61n, checkpoint61o, checkpoint61l, checkpoint61m, checkpoint61j, checkpoint61k, checkpoint61h, checkpoint61i, checkpoint61v, checkpoint61w, checkpoint61t, checkpoint61u, checkpoint61r, checkpoint61s, checkpoint61p, checkpoint61q, checkpoint61z, checkpoint61x, checkpoint61y
Changes since 1.11: +4 -3 lines
add argument "myThid" where missing

1 C $Header: /u/gcmpack/MITgcm/pkg/dic/insol.F,v 1.11 2008/04/07 20:31:16 dfer Exp $
2 C $Name: $
3
4 #include "DIC_OPTIONS.h"
5
6 CBOP
7 C !ROUTINE: INSOL
8
9 C !INTERFACE: ==========================================================
10 SUBROUTINE insol(Time,sfac,bi,bj,myThid)
11
12 C !DESCRIPTION:
13 C find light as function of date and latitude
14 c based on paltridge and parson
15
16
17 C !USES: ===============================================================
18 IMPLICIT NONE
19 C === Global variables ===
20 #include "SIZE.h"
21 #include "EEPARAMS.h"
22 #include "PARAMS.h"
23 #include "FFIELDS.h"
24 #include "GRID.h"
25 #include "DYNVARS.h"
26 #include "DIC_VARS.h"
27
28 C !INPUT PARAMETERS: ===================================================
29 C Time :: current time
30 _RL Time
31 INTEGER bi,bj
32 INTEGER myThid
33
34 C !OUPUT PARAMETERS: ===================================================
35 _RL sfac(1-OLy:sNy+OLy)
36
37 #ifdef DIC_BIOTIC
38
39 C !LOCAL VARIABLES: ====================================================
40 _RL solar, albedo
41 _RL dayfrac, yday, delta
42 _RL lat, sun1, dayhrs
43 _RL cosz, frac, fluxi
44 integer j
45 CEOP
46
47 solar = 1360. _d 0 !solar constant
48 albedo= 0.6 _d 0 !planetary albedo
49
50 #ifndef READ_PAR
51 C latitute in radians, backed out from coriolis parameter
52 C (makes latitude independent of grid)
53 IF ( usingCurvilinearGrid ) THEN
54 STOP 'S/R INSOL: use #define READ_PAR with usingCurvilinearGrid'
55 ENDIF
56 #endif /* READ_PAR */
57
58 c
59 c find day (****NOTE for year starting in winter*****)
60 dayfrac=mod(Time,360. _d 0*86400. _d 0)
61 & /(360. _d 0*86400. _d 0) !fraction of year
62 yday = 2. _d 0*PI*dayfrac !convert to radians
63 delta = (0.006918 _d 0
64 & -(0.399912 _d 0*cos(yday)) !cosine zenith angle
65 & +(0.070257 _d 0*sin(yday)) !(paltridge+platt)
66 & -(0.006758 _d 0*cos(2. _d 0*yday))
67 & +(0.000907 _d 0*sin(2. _d 0*yday))
68 & -(0.002697 _d 0*cos(3. _d 0*yday))
69 & +(0.001480 _d 0*sin(3. _d 0*yday)) )
70 DO j=1-OLy,sNy+OLy
71 c latitude in radians
72 lat=YC(1,j,1,bj)*deg2rad
73 #ifndef READ_PAR
74 C latitute in radians, backed out from coriolis parameter
75 C (makes latitude independent of grid)
76 IF ( .NOT. usingSphericalPolarGrid )
77 & lat = asin( fCori(1,j,1,bj)/(2. _d 0*omega) )*deg2rad
78 #endif /* READ_PAR */
79 sun1 = -sin(delta)/cos(delta) * sin(lat)/cos(lat)
80 IF (sun1.LE.-0.999 _d 0) sun1=-0.999 _d 0
81 IF (sun1.GE. 0.999 _d 0) sun1= 0.999 _d 0
82 dayhrs = abs(acos(sun1))
83 cosz = ( sin(delta)*sin(lat)+ !average zenith angle
84 & (cos(delta)*cos(lat)*sin(dayhrs)/dayhrs) )
85 IF (cosz.LE.5. _d -3) cosz= 5. _d -3
86 frac = dayhrs/PI !fraction of daylight in day
87 c daily average photosynthetically active solar radiation just below surface
88 fluxi = solar*(1. _d 0-albedo)*cosz*frac*parfrac
89 c
90 c convert to sfac
91 sfac(j) = MAX(1. _d -5,fluxi)
92 ENDDO !j
93
94 #endif /* DIC_BIOTIC */
95
96 return
97 end

  ViewVC Help
Powered by ViewVC 1.1.22