/[MITgcm]/MITgcm/pkg/ebm/ebm_wind_perturb.F
ViewVC logotype

Contents of /MITgcm/pkg/ebm/ebm_wind_perturb.F

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


Revision 1.4 - (show annotations) (download)
Sun Aug 28 22:18:13 2011 UTC (12 years, 8 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint64y, checkpoint64x, checkpoint64z, checkpoint64q, checkpoint64p, checkpoint64s, checkpoint64r, checkpoint64u, checkpoint64t, checkpoint64w, checkpoint64v, checkpoint64i, checkpoint64h, checkpoint64k, checkpoint64j, checkpoint64m, checkpoint64l, checkpoint64o, checkpoint64n, checkpoint64a, checkpoint64c, checkpoint64b, checkpoint64e, checkpoint64d, checkpoint64g, checkpoint64f, checkpoint63p, checkpoint63q, checkpoint63r, checkpoint63s, checkpoint63l, checkpoint63m, checkpoint63n, checkpoint63o, checkpoint63h, checkpoint63i, checkpoint63j, checkpoint63k, checkpoint63d, checkpoint63e, checkpoint63f, checkpoint63g, checkpoint63b, checkpoint63c, checkpoint64, checkpoint65, checkpoint66g, checkpoint66f, checkpoint66e, checkpoint66d, checkpoint66c, checkpoint66b, checkpoint66a, checkpoint66o, checkpoint66n, checkpoint66m, checkpoint66l, checkpoint66k, checkpoint66j, checkpoint66i, checkpoint66h, checkpoint65z, checkpoint65x, checkpoint65y, checkpoint65r, checkpoint65s, checkpoint65p, checkpoint65q, checkpoint65v, checkpoint65w, checkpoint65t, checkpoint65u, checkpoint65j, checkpoint65k, checkpoint65h, checkpoint65i, checkpoint65n, checkpoint65o, checkpoint65l, checkpoint65m, checkpoint65b, checkpoint65c, checkpoint65a, checkpoint65f, checkpoint65g, checkpoint65d, checkpoint65e, HEAD
Changes since 1.3: +23 -12 lines
add wind-stress perturbation to forcing array "fu"
 (note: does not compile, but was not compiling before neither)

1 C $Header: /u/gcmpack/MITgcm/pkg/ebm/ebm_wind_perturb.F,v 1.3 2009/04/28 18:11:51 jmc Exp $
2 C $Name: $
3
4 #include "EBM_OPTIONS.h"
5
6 CStartOfInterface
7 SUBROUTINE EBM_WIND_PERTURB( myTime, myIter, myThid )
8 C *==========================================================*
9 C | S/R EBM_WIND_PERTURB
10 C | o Calculated random wind perturbations.
11 C *==========================================================*
12 IMPLICIT NONE
13
14 C == Global data ==
15 #include "SIZE.h"
16 #include "EEPARAMS.h"
17 #include "PARAMS.h"
18 #include "GRID.h"
19 #include "DYNVARS.h"
20 #include "FFIELDS.h"
21 #ifdef ALLOW_EBM
22 # include "EBM.h"
23 #endif
24
25 C == Routine arguments ==
26 _RL myTime
27 INTEGER myIter
28 INTEGER myThid
29 CEndOfInterface
30
31 #ifdef ALLOW_EBM
32 # ifdef EBM_WIND_PERT
33
34 C == Local variables ==
35 C Loop counters
36 INTEGER i, j, bi, bj
37 _RS ya(1-OLy:sNy+OLy), ya2(1-OLy:sNy+OLy)
38 _RS xa(1-OLx:sNx+OLx), xa2(1-OLx:sNx+OLx)
39 _RS y(1-OLy:sNy+OLy), x(1-OLx:sNx+OLx)
40 _RS temp(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
41 _RS temp2(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
42 _RS stdev(1-OLy:sNy+OLy)
43 _RS std(1:40)
44 data std /0.030, 0.035, 0.045, 0.053, 0.059, 0.060, 0.056,
45 & 0.048, 0.041, 0.038, 0.034, 0.029, 0.023, 0.018,
46 & 0.016, 0.015, 0.013, 0.011, 0.008, 0.005, 0.005,
47 & 0.005, 0.008, 0.011, 0.014, 0.014, 0.017, 0.019,
48 & 0.023, 0.029, 0.032, 0.038, 0.048, 0.058, 0.065,
49 & 0.067, 0.063, 0.060, 0.062, 0.064 /
50
51
52 DO bj=myByLo(myThid),myByHi(myThid)
53 DO bi=myBxLo(myThid),myBxHi(myThid)
54
55 DO j = 1-OLy, sNy+OLy
56 y(j) = 0.0
57 ya(j) = 0.0
58 ya2(j) = 0.0
59 stdev(j) = 0.0
60 ENDDO
61 DO i = 1-OLx, sNx+OLx
62 x(i) = 0.0
63 xa(i) = 0.0
64 xa2(i) = 0.0
65 ENDDO
66 DO i = 1-OLx, sNx+OLx
67 DO j = 1-OLy, sNy+OLy
68 temp(i,j) = 0.0
69 temp2(i,j) = 0.0
70 ENDDO
71 ENDDO
72 DO j = 1, sNy
73 stdev(j) = std(j)
74 ENDDO
75
76 cph Generate random numbers
77 cph Need to get this from somewhere!
78 call random_number (temp)
79
80 C interpolation in first dimension
81 C scaling to get a process with a standard deviation of 1
82 DO j = jMin, jMax
83 DO i = iMin, iMax
84 temp(i,j) = 1.73*(2.0*temp(i,j) - 1.0)
85 ENDDO
86 ENDDO
87
88 DO j = jMin, jMax
89 DO i = iMin, iMax
90 x(i) = i
91 xa(i) = x(i) - MOD(x(i),10.0)
92 xa2(i) = xa(i)+10.0
93 if ( xa2(i) .gt. sNx+Olx ) then
94 xa2(i) = 0.0
95 endif
96 temp2(i,j) = 0.1*( (x(i)-xa(i))*temp(INT(xa2(i)),j)+
97 & (10.0-x(i)+xa(i))*temp(INT(xa(i)),j) )
98 ENDDO
99 ENDDO
100
101 C interpolation in second dimension
102 C multiplication with observation zonal wind stress standard deviation
103 C add AR1 process
104 DO i = iMin, iMax
105 DO j = jMin, jMax
106 y(j) = j
107 ya(j) = y(j) - MOD(y(j),6.0)
108 ya2(j) = ya(j)+6.0
109 if ( ya2(j) .gt. sNy+Oly ) then
110 ya2(j) = 0.0
111 endif
112 c time lag correlation coefficient, use 0.75 for temperature timescale,
113 c 0.98 for the momentum timescale.
114 winPert(i,j,bi,bj) = maskW(i,j,k,bi,bj)*
115 & (1.0/1.66)*(0.75*winPert(i,j,bi,bj) +
116 & stdev(j)*(1.0/6.0)*
117 & ((y(j)-ya(j))*temp2(i,INT(ya2(j)))+
118 & (6.0-y(j)+ya(j))*temp2(i,INT(ya(j)))))
119 ENDDO
120 ENDDO
121
122 ENDDO
123 ENDDO
124
125 C CALL PLOT_FIELD_XYRS( winPert, 'winPert',1,myThid)
126
127 _EXCH_XY_RS(winPert , myThid )
128
129 DO bj=myByLo(myThid),myByHi(myThid)
130 DO bi=myBxLo(myThid),myBxHi(myThid)
131 DO j = 1-OLy, sNy+OLy
132 DO i = 1-OLx, sNx+OLx
133 fu(i,j,bi,bj) = fu(i,j,bi,bj)
134 & + winPert(i,j,bi,bj)*rUnit2mass
135 & *drF(1)*hFacW(i,j,1,bi,bj)
136 ENDDO
137 ENDDO
138 ENDDO
139 ENDDO
140
141 # endif /* EBM_WIND_PERT */
142 #endif /* ALLOW_EBM */
143
144 RETURN
145 END

  ViewVC Help
Powered by ViewVC 1.1.22