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

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

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


Revision 1.1.4.4 - (hide annotations) (download)
Sun Jan 12 08:20:10 2003 UTC (21 years, 4 months ago) by dimitri
Branch: release1
CVS Tags: release1_p11
Changes since 1.1.4.3: +2 -2 lines
  - improved description of the various forcing configurations
  - added basic radiation bulk formulae to pkg/exf

1 dimitri 1.1.4.4 c $Header: /u/gcmpack/MITgcm/pkg/exf/exf_set_climsalt.F,v 1.1.4.3 2002/12/27 08:01:55 dimitri Exp $
2 heimbach 1.1
3     #include "EXF_CPPOPTIONS.h"
4    
5    
6     subroutine exf_set_climsalt(
7 heimbach 1.1.4.2 O mycurrenttime
8 heimbach 1.1 I , mycurrentiter
9     I , mythid
10     & )
11    
12     c ==================================================================
13     c SUBROUTINE exf_set_climsalt
14     c ==================================================================
15     c
16     c o Get the current climatological sea surface salinity field.
17     c
18     c started: Christian Eckert eckert@mit.edu 27-Aug-1999
19     c changed: Christian Eckert eckert@mit.edu 11-Jan-2000
20     c - Restructured the code in order to create a package
21     c for the MITgcmUV.
22     c Christian Eckert eckert@mit.edu 12-Feb-2000
23     c - Changed Routine names (package prefix: exf_)
24 heimbach 1.1.4.2 c changed: heimbach@mit.edu 08-Feb-2002
25 dimitri 1.1.4.4 c mods for pkg/seaice: menemenlis@jpl.nasa.gov 20-Dec-2002
26 heimbach 1.1 c
27     c ==================================================================
28     c SUBROUTINE exf_set_climsalt
29     c ==================================================================
30    
31     implicit none
32    
33     #include "EEPARAMS.h"
34     #include "SIZE.h"
35     #include "GRID.h"
36    
37     #include "exf_param.h"
38     #include "exf_constants.h"
39     #include "exf_clim_param.h"
40 heimbach 1.1.4.2 #include "exf_clim_fields.h"
41 heimbach 1.1
42     c == routine arguments ==
43    
44     _RL mycurrenttime
45     integer mycurrentiter
46     integer mythid
47    
48     #ifdef ALLOW_CLIMSALT_RELAXATION
49    
50     c == local variables ==
51    
52     logical first, changed
53     integer count0, count1
54     _RL fac
55    
56     integer bi, bj
57     integer i, j, k
58    
59     c == end of interface ==
60    
61 heimbach 1.1.4.1 #ifdef ALLOW_CLIM_CYCLIC
62     c record numbers are assumed 1 to 12 corresponding to
63     c Jan. through Dec.
64     call cal_GetMonthsRec(
65     O fac, first, changed,
66     O count0, count1,
67     I mycurrenttime, mycurrentiter, mythid
68     & )
69     #else
70 heimbach 1.1 c get record numbers and interpolation factor for climsalt
71     call exf_GetFFieldRec(
72     I climsaltstartdate, climsaltperiod
73     O , fac, first, changed
74     O , count0, count1
75     I , mycurrenttime, mycurrentiter, mythid
76     & )
77 heimbach 1.1.4.1 #endif
78 heimbach 1.1
79     if ( first ) then
80 heimbach 1.1.4.2 if ( climsaltfile .NE. ' ' )
81     & call mdsreadfield( climsaltfile, exf_clim_iprec
82 heimbach 1.1 & , exf_clim_yftype, nr
83     & , climsalt1, count0, mythid
84     & )
85     if (exf_clim_yftype .eq. 'RL') then
86     call exf_filter_rl( climsalt1, climsaltmask, mythid )
87     else
88     call exf_filter_rs( climsalt1, climsaltmask, mythid )
89     end if
90     endif
91    
92     if (( first ) .or. ( changed )) then
93     call exf_SwapFFields_3d( climsalt0, climsalt1, mythid )
94    
95 heimbach 1.1.4.2 if ( climsaltfile .NE. ' ' )
96     & call mdsreadfield( climsaltfile, exf_clim_iprec
97 heimbach 1.1 & , exf_clim_yftype, nr
98     & , climsalt1, count1, mythid
99     & )
100     if (exf_clim_yftype .eq. 'RL') then
101     call exf_filter_rl( climsalt1, climsaltmask, mythid )
102     else
103     call exf_filter_rs( climsalt1, climsaltmask, mythid )
104     end if
105     endif
106    
107     c Loop over tiles.
108     do bj = mybylo(mythid),mybyhi(mythid)
109     do bi = mybxlo(mythid),mybxhi(mythid)
110     do k = 1,nr
111     do j = 1-oly,sny+oly
112     do i = 1-olx,snx+olx
113    
114     c Interpolate linearly onto the current time.
115     climsalt(i,j,k,bi,bj) =
116     & fac *climsalt0(i,j,k,bi,bj)+
117     & (exf_one - fac) *climsalt1(i,j,k,bi,bj)
118    
119     enddo
120     enddo
121     enddo
122     enddo
123     enddo
124    
125     #endif /* ALLOW_CLIMSALT_RELAXATION */
126    
127     end
128    
129    
130     subroutine exf_init_climsalt(
131     I mythid
132     & )
133    
134     c ==================================================================
135     c SUBROUTINE exf_init_climsalt
136     c ==================================================================
137     c
138     c o
139     c
140     c started: Ralf.Giering@FastOpt.de 25-Mai-2000
141     c
142     c ==================================================================
143     c SUBROUTINE exf_init_climsalt
144     c ==================================================================
145    
146     implicit none
147    
148     c == global variables ==
149    
150     #include "EEPARAMS.h"
151     #include "SIZE.h"
152    
153     #include "exf_fields.h"
154     #include "exf_param.h"
155     #include "exf_clim_fields.h"
156    
157     c == routine arguments ==
158    
159     integer mythid
160    
161     #ifdef ALLOW_CLIMSALT_RELAXATION
162    
163     c == local variables ==
164    
165     integer bi, bj
166     integer i, j, k
167    
168     c == end of interface ==
169    
170     do bj = mybylo(mythid), mybyhi(mythid)
171     do bi = mybxlo(mythid), mybxhi(mythid)
172     do k=1,nr
173     do j = 1, sny
174     do i = 1, snx
175     climsalt (i,j,k,bi,bj) = 0. _d 0
176     climsalt0(i,j,k,bi,bj) = 0. _d 0
177     climsalt1(i,j,k,bi,bj) = 0. _d 0
178     enddo
179     enddo
180     enddo
181     enddo
182     enddo
183    
184     #endif /* ALLOW_CLIMSALT_RELAXATION */
185    
186     end

  ViewVC Help
Powered by ViewVC 1.1.22