/[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.12 - (hide annotations) (download)
Wed Mar 17 23:08:09 2004 UTC (20 years, 2 months ago) by dimitri
Branch: MAIN
CVS Tags: checkpoint53f_post, checkpoint54a_pre, checkpoint55c_post, checkpoint53b_pre, checkpoint52n_post, checkpoint53c_post, checkpoint53d_post, checkpoint55d_pre, checkpoint54a_post, checkpoint54b_post, checkpoint54d_post, checkpoint54e_post, checkpoint55b_post, checkpoint52m_post, checkpoint55, checkpoint53a_post, checkpoint55a_post, checkpoint53b_post, checkpoint54, checkpoint53, checkpoint53g_post, checkpoint54f_post, checkpoint53d_pre, checkpoint54c_post
Changes since 1.11: +19 -15 lines
o Added capability to read-in both atmospheric fluxes and atmospheric
  conditions, needed for running sea-ice model in conjunction with fluxes.
o Removed ALLOW_CLIM_CYCLIC: cyclic monthly forcing is instead diagnosed
  from presence or absence of input parameters clim*period

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

  ViewVC Help
Powered by ViewVC 1.1.22