/[MITgcm]/MITgcm/pkg/atm_compon_interf/atm_store_aim_wndstr.F
ViewVC logotype

Annotation of /MITgcm/pkg/atm_compon_interf/atm_store_aim_wndstr.F

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


Revision 1.1 - (hide annotations) (download)
Wed Sep 11 20:17:27 2013 UTC (10 years, 8 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint64y, checkpoint64x, checkpoint64z, checkpoint64o, checkpoint64q, checkpoint64p, checkpoint64s, checkpoint64r, checkpoint64u, checkpoint64t, checkpoint64w, checkpoint64v, checkpoint65p, checkpoint65j, checkpoint65k, checkpoint65h, checkpoint65i, checkpoint65n, checkpoint65o, checkpoint65l, checkpoint65m, checkpoint65b, checkpoint65c, checkpoint65a, checkpoint65f, checkpoint65g, checkpoint65d, checkpoint65e, checkpoint65
- regroup per field origin (model & pkgs) the coupling storage routines
   (which accumalate in time each coupling field)
- move bi,bj loops inside atm_store_my_data.F and store alos wind-stress;
  update accordingly + simplify aim_do_physics.F

1 jmc 1.1 C $Header: /u/gcmpack/MITgcm/pkg/atm_compon_interf/atm_store_taux.F,v 1.2 2004/05/21 20:00:48 jmc Exp $
2     C $Name: $
3    
4     #include "PACKAGES_CONFIG.h"
5     #include "CPP_OPTIONS.h"
6     #ifdef ALLOW_AIM
7     # include "AIM_OPTIONS.h"
8     #endif
9    
10     CBOP
11     C !ROUTINE: ATM_STORE_AIM_WNDSTR
12     C !INTERFACE:
13     SUBROUTINE ATM_STORE_AIM_WNDSTR(
14     I bi, bj,
15     I myTime, myIter, myThid )
16    
17     C !DESCRIPTION: \bv
18     C *==========================================================*
19     C | SUBROUTINE ATM_STORE_AIM_WNDSTR
20     C | o Routine for saving AIM surface wind-stress fields
21     C | for export to coupling layer.
22     C *==========================================================*
23     C | This version interfaces to the AIM package.
24     C *==========================================================*
25    
26     C !USES:
27     IMPLICIT NONE
28    
29     C == Global variables ==
30     #ifdef ALLOW_AIM
31     # include "AIM_SIZE.h"
32     #else
33     # include "SIZE.h"
34     #endif
35    
36     #include "EEPARAMS.h"
37     #include "PARAMS.h"
38     #include "CPL_PARAMS.h"
39     #include "GRID.h"
40     #include "DYNVARS.h"
41     #ifdef ALLOW_AIM
42     # include "AIM2DYN.h"
43     c #include "AIM_FFIELDS.h"
44     #endif
45     #ifdef ALLOW_THSICE
46     # include "THSICE_PARAMS.h"
47     # include "THSICE_VARS.h"
48     #endif
49     C == Global variables for coupling interface ==
50     #include "ATMCPL.h"
51    
52     C !INPUT/OUTPUT PARAMETERS:
53     C bi, bj :: Tile indices
54     C myTime :: Current time in simulation (s)
55     C myIter :: Current iteration number
56     C myThid :: My Thread Id. number
57     INTEGER bi, bj
58     _RL myTime
59     INTEGER myIter
60     INTEGER myThid
61     CEOP
62    
63     #ifdef ALLOW_AIM
64     C !LOCAL VARIABLES:
65     C i, j :: Loop counters
66     C ks :: surface level index
67     INTEGER i, j, ks
68     _RL cplTimeFraction
69     _RL uStr_tmp, vStr_tmp
70    
71     C o Accumulate momentum surface flux that will be exported to the
72     C coupling layer. Momentum flux is in N/m^2 with same sign as the wind.
73     cplTimeFraction = 1. _d 0 / DFLOAT(cplSendFrq_iter)
74     ks = 1
75    
76     tauXTime(bi,bj) = tauXTime(bi,bj) + cplTimeFraction
77     tauYTime(bi,bj) = tauYTime(bi,bj) + cplTimeFraction
78     #ifdef ALLOW_THSICE
79     IF ( useThSIce .AND. stressReduction.GT. 0. _d 0 ) THEN
80     C-- Reduce wind stress applied to ocean where sea-ice is present
81     DO j=1,sNy
82     DO i=1,sNx
83     c IF ( aim_landFr(i-1,j,bi,bj)*aim_landFr(i,j,bi,bj) .NE. 1. ) THEN
84     IF ( hFacW(i,j,ks,bi,bj) .NE. 0. ) THEN
85     uStr_tmp =
86     & ( aim_drag(i-1,j,bi,bj)
87     & *(1. _d 0 - iceMask(i-1,j,bi,bj)*stressReduction)
88     & + aim_drag( i ,j,bi,bj)
89     & *(1. _d 0 - iceMask( i ,j,bi,bj)*stressReduction)
90     & )* 0.5 _d 0 * uVel(i,j,ks,bi,bj)
91     tauX(i,j,bi,bj) = tauX(i,j,bi,bj)
92     & + uStr_tmp*cplTimeFraction
93     ENDIF
94     ENDDO
95     ENDDO
96     DO j=1,sNy
97     DO i=1,sNx
98     c IF ( aim_landFr(i,j-1,bi,bj)*aim_landFr(i,j,bi,bj) .NE. 1. ) THEN
99     IF ( hFacS(i,j,ks,bi,bj) .NE. 0. ) THEN
100     vStr_tmp =
101     & ( aim_drag(i,j-1,bi,bj)
102     & *(1. _d 0 - iceMask(i,j-1,bi,bj)*stressReduction)
103     & + aim_drag(i, j ,bi,bj)
104     & *(1. _d 0 - iceMask(i, j ,bi,bj)*stressReduction)
105     & )* 0.5 _d 0 * vVel(i,j,ks,bi,bj)
106     tauY(i,j,bi,bj) = tauY(i,j,bi,bj)
107     & + vStr_tmp*cplTimeFraction
108     ENDIF
109     ENDDO
110     ENDDO
111     ELSE
112     #else /*ALLOW_THSICE*/
113     IF (.TRUE.) THEN
114     #endif /*ALLOW_THSICE*/
115     DO j=1,sNy
116     DO i=1,sNx
117     c IF ( aim_landFr(i-1,j,bi,bj)*aim_landFr(i,j,bi,bj) .NE. 1. ) THEN
118     IF ( hFacW(i,j,ks,bi,bj) .NE. 0. ) THEN
119     uStr_tmp =
120     & ( aim_drag(i-1,j,bi,bj)+aim_drag(i,j,bi,bj) )
121     & * 0.5 _d 0 * uVel(i,j,ks,bi,bj)
122     tauX(i,j,bi,bj) = tauX(i,j,bi,bj)
123     & + uStr_tmp*cplTimeFraction
124     ENDIF
125     ENDDO
126     ENDDO
127     DO j=1,sNy
128     DO i=1,sNx
129     c IF ( aim_landFr(i,j-1,bi,bj)*aim_landFr(i,j,bi,bj) .NE. 1. ) THEN
130     IF ( hFacS(i,j,ks,bi,bj) .NE. 0. ) THEN
131     vStr_tmp =
132     & ( aim_drag(i,j-1,bi,bj)+aim_drag(i,j,bi,bj) )
133     & * 0.5 _d 0 * vVel(i,j,ks,bi,bj)
134     tauY(i,j,bi,bj) = tauY(i,j,bi,bj)
135     & + vStr_tmp*cplTimeFraction
136     ENDIF
137     ENDDO
138     ENDDO
139     ENDIF
140    
141     #endif /* ALLOW_AIM */
142    
143     RETURN
144     END

  ViewVC Help
Powered by ViewVC 1.1.22