/[MITgcm]/MITgcm/pkg/exf/exf_set_climsst.F
ViewVC logotype

Annotation of /MITgcm/pkg/exf/exf_set_climsst.F

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


Revision 1.1 - (hide annotations) (download)
Mon May 14 22:08:41 2001 UTC (23 years ago) by heimbach
Branch: MAIN
CVS Tags: release1-branch_tutorials, checkpoint40pre1, checkpoint43a-release1mods, chkpt44a_pre, release1-branch-end, checkpoint44, checkpoint40pre2, checkpoint40pre5, checkpoint40pre6, checkpoint40pre8, release1_b1, checkpoint42, checkpoint43, chkpt44a_post, checkpoint44b_pre, checkpoint40pre4, ecco-branch-mod1, checkpoint40pre3, checkpoint40pre9, ecco-branch-mod2, ecco-branch-mod3, release1_beta1, release1-branch_branchpoint, checkpoint40pre7, checkpoint40, checkpoint39, checkpoint41
Branch point for: ecco-branch, release1_coupled, release1-branch, release1
Added external forcing package.
Not presently supported by mitgcm, i.e. disabled by default.

1 heimbach 1.1 c $Header: /u/gcmpack/development/heimbach/ecco_env/pkg/exf/exf_set_climsst.F,v 1.1 2001/02/02 19:43:47 heimbach Exp $
2    
3     #include "EXF_CPPOPTIONS.h"
4    
5    
6     subroutine exf_set_climsst(
7     O climsst
8     I , mycurrenttime
9     I , mycurrentiter
10     I , mythid
11     & )
12    
13     c ==================================================================
14     c SUBROUTINE exf_set_climsst
15     c ==================================================================
16     c
17     c o Get the current climatological sea surface salinity field.
18     c
19     c started: Christian Eckert eckert@mit.edu 27-Aug-1999
20     c
21     c changed: Christian Eckert eckert@mit.edu 11-Jan-2000
22     c
23     c - Restructured the code in order to create a package
24     c for the MITgcmUV.
25     c
26     c Christian Eckert eckert@mit.edu 12-Feb-2000
27     c
28     c - Changed Routine names (package prefix: exf_)
29     c
30     c ==================================================================
31     c SUBROUTINE exf_set_climsst
32     c ==================================================================
33    
34     implicit none
35    
36     #include "EEPARAMS.h"
37     #include "SIZE.h"
38     #include "GRID.h"
39    
40     #include "exf_param.h"
41     #include "exf_constants.h"
42     #include "exf_clim_param.h"
43    
44     c == routine arguments ==
45    
46     _RL climsst(1-olx:snx+olx,1-oly:sny+oly,nsx,nsy)
47     _RL mycurrenttime
48     integer mycurrentiter
49     integer mythid
50    
51     #ifdef ALLOW_CLIMSST_RELAXATION
52    
53     c == local variables ==
54    
55     common /exf_csst_r/ climsst0, climsst1
56     _RL climsst0(1-olx:snx+olx,1-oly:sny+oly,nsx,nsy)
57     _RL climsst1(1-olx:snx+olx,1-oly:sny+oly,nsx,nsy)
58    
59     logical first, changed
60     integer count0, count1
61     _RL fac
62    
63     integer bi, bj
64     integer i, j
65    
66     c == end of interface ==
67    
68    
69     cph(
70     cph Routine exf_GetSSTClimRec has standard cyclic forcing
71     cph assuming 12 monthly climatological records on file
72     cph with irec=1: Jan, ... irec=12: Dec
73     cph Will be included as optional choice of to the above.
74     cph
75     cph call exf_GetSSTClimRec(
76     cph O fac, first, changed,
77     cph O count0,count1,
78     cph I mytime, myiter, mythid
79     cph & )
80     cph)
81    
82    
83     c get record numbers and interpolation factor for climsst
84     call exf_GetFFieldRec(
85     I climsststartdate, climsstperiod
86     O , fac, first, changed
87     O , count0, count1
88     I , mycurrenttime, mycurrentiter, mythid
89     & )
90    
91     if ( first ) then
92     call mdsreadfield( climsstfile, exf_clim_iprec
93     & , exf_clim_yftype, 1
94     & , climsst1, count0, mythid
95     & )
96     if (exf_clim_yftype .eq. 'RL') then
97     call exf_filter_rl( climsst1, climsstmask, mythid )
98     else
99     call exf_filter_rs( climsst1, climsstmask, mythid )
100     end if
101     endif
102    
103     if (( first ) .or. ( changed )) then
104     call exf_SwapFFields( climsst0, climsst1, mythid )
105    
106     call mdsreadfield( climsstfile, exf_clim_iprec
107     & , exf_clim_yftype, 1
108     & , climsst1, count1, mythid
109     & )
110     if (exf_clim_yftype .eq. 'RL') then
111     call exf_filter_rl( climsst1, climsstmask, mythid )
112     else
113     call exf_filter_rs( climsst1, climsstmask, mythid )
114     end if
115     endif
116    
117     c Loop over tiles.
118     do bj = mybylo(mythid),mybyhi(mythid)
119     do bi = mybxlo(mythid),mybxhi(mythid)
120     do j = 1-oly,sny+oly
121     do i = 1-olx,snx+olx
122    
123     c Set to freezing temperature if less
124     if (climsst0(i,j,bi,bj) .lt. climtempfreeze) then
125     climsst0(i,j,bi,bj) = climtempfreeze
126     endif
127     if (climsst1(i,j,bi,bj) .lt. climtempfreeze) then
128     climsst1(i,j,bi,bj) = climtempfreeze
129     endif
130    
131     c Interpolate linearly onto the current time.
132     climsst(i,j,bi,bj) = fac *climsst0(i,j,bi,bj)+
133     & (exf_one - fac) *climsst1(i,j,bi,bj)
134    
135     enddo
136     enddo
137     enddo
138     enddo
139    
140     #endif /* ALLOW_CLIMSST_RELAXATION */
141    
142     end
143    
144    
145     subroutine exf_init_climsst(
146     I mythid
147     & )
148    
149     c ==================================================================
150     c SUBROUTINE exf_init_climsst
151     c ==================================================================
152     c
153     c o
154     c
155     c started: Ralf.Giering@FastOpt.de 25-Mai-2000
156     c
157     c ==================================================================
158     c SUBROUTINE exf_init_climsst
159     c ==================================================================
160    
161     implicit none
162    
163     c == global variables ==
164    
165     #include "EEPARAMS.h"
166     #include "SIZE.h"
167    
168     #include "exf_fields.h"
169     #include "exf_param.h"
170     #include "exf_clim_param.h"
171     #include "exf_clim_fields.h"
172    
173     c == routine arguments ==
174    
175     integer mythid
176    
177     #ifdef ALLOW_CLIMSST_RELAXATION
178    
179     c == local variables ==
180    
181     common /exf_csst_r/ climsst0, climsst1
182     _RL climsst0(1-olx:snx+olx,1-oly:sny+oly,nsx,nsy)
183     _RL climsst1(1-olx:snx+olx,1-oly:sny+oly,nsx,nsy)
184    
185     integer bi, bj
186     integer i, j
187    
188     c == end of interface ==
189    
190     do bj = mybylo(mythid), mybyhi(mythid)
191     do bi = mybxlo(mythid), mybxhi(mythid)
192     do j = 1, sny
193     do i = 1, snx
194     climsst (i,j,bi,bj) = 0. _d 0
195     climsst0(i,j,bi,bj) = 0. _d 0
196     climsst1(i,j,bi,bj) = 0. _d 0
197     enddo
198     enddo
199     enddo
200     enddo
201    
202     #endif /* ALLOW_CLIMSSST_RELAXATION */
203    
204     end

  ViewVC Help
Powered by ViewVC 1.1.22