/[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.6 - (hide annotations) (download)
Thu Mar 6 00:47:33 2003 UTC (21 years, 2 months ago) by heimbach
Branch: MAIN
CVS Tags: checkpoint50e_post, checkpoint50c_post, checkpoint50c_pre, checkpoint50h_post, checkpoint50d_pre, checkpoint50b_pre, checkpoint51e_post, checkpoint51b_post, checkpoint51c_post, checkpoint49, checkpoint50i_post, checkpoint51, checkpoint50, checkpoint50d_post, checkpoint51b_pre, checkpoint50g_post, checkpoint50b_post, checkpoint50f_post, checkpoint50f_pre, checkpoint51d_post, checkpoint50a_post, checkpoint51a_post, checkpoint50e_pre
Changes since 1.5: +2 -2 lines
merged from ecco-branch:
o exf:
  - Enable initialisation of forcing fields to constant
    (runtime) values.
  - in exf_getffields.F
    Reduce i-/j-loop to interior domain, discarding overlaps.
    That also fixes wrong TAF-key computations for key_1, key_2
    with bulf formulae.
  - exf_init.F modify #ifdef for exf_init_evap
  - exf_getffieldrec.F, ctrl_getrec.F
    The following INT-usages are not safe:
      fldsecs  = int(fldsecs/fldperiod)*fldperiod
      fldcount = int(fldsecs/fldperiod) + 1
    and were modified.

1 heimbach 1.6 c $Header: /u/gcmpack/MITgcm/pkg/exf/exf_set_climsst.F,v 1.1.6.5 2003/03/04 00:17:40 heimbach Exp $
2 heimbach 1.1
3     #include "EXF_CPPOPTIONS.h"
4    
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    
55     integer bi, bj
56     integer i, j
57    
58     c == end of interface ==
59    
60 dimitri 1.5 if ( climsstfile .NE. ' ' ) then
61    
62 heimbach 1.2 #ifdef ALLOW_CLIM_CYCLIC
63     c record numbers are assumed 1 to 12 corresponding to
64     c Jan. through Dec.
65 dimitri 1.5 call cal_GetMonthsRec(
66     O fac, first, changed,
67     O count0, count1,
68     I mycurrenttime, mycurrentiter, mythid
69     & )
70     #else
71 heimbach 1.1 c get record numbers and interpolation factor for climsst
72 dimitri 1.5 call exf_GetFFieldRec(
73     I climsststartdate, climsstperiod
74     O , fac, first, changed
75     O , count0, count1
76     I , mycurrenttime, mycurrentiter, mythid
77     & )
78 heimbach 1.2 #endif
79 heimbach 1.1
80 dimitri 1.5 if ( first ) then
81     call mdsreadfield( climsstfile, exf_clim_iprec
82     & , exf_clim_yftype, 1
83     & , climsst1, count0, mythid
84     & )
85     if (exf_clim_yftype .eq. 'RL') then
86     call exf_filter_rl( climsst1, climsstmask, mythid )
87     else
88     call exf_filter_rs( climsst1, climsstmask, mythid )
89     end if
90     endif
91    
92     if (( first ) .or. ( changed )) then
93     call exf_SwapFFields( climsst0, climsst1, mythid )
94     call mdsreadfield( climsstfile, exf_clim_iprec
95     & , exf_clim_yftype, 1
96     & , climsst1, count1, mythid
97     & )
98     if (exf_clim_yftype .eq. 'RL') then
99     call exf_filter_rl( climsst1, climsstmask, mythid )
100     else
101     call exf_filter_rs( climsst1, climsstmask, mythid )
102     end if
103     endif
104 heimbach 1.1
105     c Loop over tiles.
106 dimitri 1.5 do bj = mybylo(mythid),mybyhi(mythid)
107     do bi = mybxlo(mythid),mybxhi(mythid)
108     do j = 1,sny
109     do i = 1,snx
110    
111     c Set to freezing temperature if less
112     if (climsst0(i,j,bi,bj) .lt. climtempfreeze) then
113     climsst0(i,j,bi,bj) = climtempfreeze
114     endif
115     if (climsst1(i,j,bi,bj) .lt. climtempfreeze) then
116     climsst1(i,j,bi,bj) = climtempfreeze
117     endif
118    
119     c Interpolate linearly onto the current time.
120     climsst(i,j,bi,bj) = exf_inscal_sst * (
121     & fac * climsst0(i,j,bi,bj) +
122     & (exf_one - fac) * climsst1(i,j,bi,bj) )
123 heimbach 1.1
124 dimitri 1.5 enddo
125     enddo
126 heimbach 1.1 enddo
127 dimitri 1.5 enddo
128    
129     endif
130 heimbach 1.1
131     #endif /* ALLOW_CLIMSST_RELAXATION */
132    
133     end
134    
135    
136     subroutine exf_init_climsst(
137     I mythid
138     & )
139    
140     c ==================================================================
141     c SUBROUTINE exf_init_climsst
142     c ==================================================================
143     c
144     c o
145     c
146     c started: Ralf.Giering@FastOpt.de 25-Mai-2000
147     c
148     c ==================================================================
149     c SUBROUTINE exf_init_climsst
150     c ==================================================================
151    
152     implicit none
153    
154     c == global variables ==
155    
156     #include "EEPARAMS.h"
157     #include "SIZE.h"
158    
159     #include "exf_fields.h"
160     #include "exf_param.h"
161     #include "exf_clim_param.h"
162     #include "exf_clim_fields.h"
163    
164     c == routine arguments ==
165    
166     integer mythid
167    
168     #ifdef ALLOW_CLIMSST_RELAXATION
169    
170     c == local variables ==
171    
172     integer bi, bj
173     integer i, j
174    
175     c == end of interface ==
176    
177     do bj = mybylo(mythid), mybyhi(mythid)
178     do bi = mybxlo(mythid), mybxhi(mythid)
179     do j = 1, sny
180     do i = 1, snx
181 heimbach 1.6 climsst (i,j,bi,bj) = climsstconst
182 heimbach 1.1 climsst0(i,j,bi,bj) = 0. _d 0
183     climsst1(i,j,bi,bj) = 0. _d 0
184     enddo
185     enddo
186     enddo
187     enddo
188    
189     #endif /* ALLOW_CLIMSSST_RELAXATION */
190    
191     end

  ViewVC Help
Powered by ViewVC 1.1.22