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

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

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


Revision 1.2 - (hide annotations) (download)
Tue Sep 24 19:28:34 2013 UTC (10 years, 8 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint64y, checkpoint64x, checkpoint64z, checkpoint64q, checkpoint64p, checkpoint64s, checkpoint64r, checkpoint64u, checkpoint64t, checkpoint64w, checkpoint64v, checkpoint64o, checkpoint65, checkpoint65p, checkpoint65j, checkpoint65k, checkpoint65h, checkpoint65i, checkpoint65n, checkpoint65o, checkpoint65l, checkpoint65m, checkpoint65b, checkpoint65c, checkpoint65a, checkpoint65f, checkpoint65g, checkpoint65d, checkpoint65e
Changes since 1.1: +31 -19 lines
enable to be used with pkg/atm_phys (gray atmosphere)

1 jmc 1.2 C $Header: /u/gcmpack/MITgcm/pkg/atm_compon_interf/atm_apply_import.F,v 1.1 2004/05/21 19:59:38 jmc Exp $
2 jmc 1.1 C $Name: $
3    
4     #include "PACKAGES_CONFIG.h"
5     #include "CPP_OPTIONS.h"
6    
7     CBOP
8     C !ROUTINE: ATM_APPLY_IMPORT
9     C !INTERFACE:
10 jmc 1.2 SUBROUTINE ATM_APPLY_IMPORT(
11 jmc 1.1 I land_frc,
12 jmc 1.2 U atmSST, atmSIfrc,
13 jmc 1.1 I myTime, myIter, bi, bj, myThid )
14    
15     C !DESCRIPTION: \bv
16     C *================================================================*
17     C | S/R ATM_APPLY_IMPORT
18 jmc 1.2 C | o Apply imported coupling data to ATM surface BC over ocean
19 jmc 1.1 C *================================================================*
20     C | Note: when using sea-ice, fill in Mixed layer fields instead
21 jmc 1.2 C | to be used later as SST by Atmos. + Sea-Ice
22 jmc 1.1 C *================================================================*
23     C \ev
24    
25     C !USES:
26     IMPLICIT NONE
27    
28     C == Global variables ===
29     #include "SIZE.h"
30     #include "EEPARAMS.h"
31     #include "PARAMS.h"
32     #include "CPL_PARAMS.h"
33    
34     #ifdef ALLOW_THSICE
35     # include "THSICE_VARS.h"
36     #endif
37    
38     C-- Coupled to the Ocean :
39     #include "ATMCPL.h"
40    
41     C !INPUT/OUTPUT PARAMETERS:
42     C == Routine arguments ==
43     C land_frc :: land fraction [0-1]
44 jmc 1.2 C atmSST :: sea surface temp [K], used in ATM component
45     C atmSIfrc :: sea-ice fraction [0-1], used in ATM component
46 jmc 1.1 C myTime :: Current time of simulation ( s )
47     C myIter :: Current iteration number in simulation
48     C bi,bj :: Tile index
49     C myThid :: Number of this instance of the routine
50     _RS land_frc(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
51 jmc 1.2 _RL atmSST (sNx,sNy)
52     _RL atmSIfrc(sNx,sNy)
53 jmc 1.1 _RL myTime
54     INTEGER myIter, bi, bj, myThid
55     CEOP
56    
57     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
58    
59     #ifdef COMPONENT_MODULE
60     C == Local variables ==
61     C i,j :: Loop counters
62     INTEGER i,j
63    
64     #ifdef ALLOW_THSICE
65     IF ( useThSIce ) THEN
66     C-- Put fields from the ocean component in Mixed-layer arrays:
67    
68     C- fill in hOceMxL with Mixed-layer Depth from the ocean component
69 jmc 1.2 IF ( useImportMxlD ) THEN
70 jmc 1.1 DO j=1,sNy
71     DO i=1,sNx
72     IF ( land_frc(i,j,bi,bj) .LT. 1. ) THEN
73     hOceMxL(i,j,bi,bj) = ocMxlD(i,j,bi,bj)
74     ENDIF
75     ENDDO
76     ENDDO
77     ENDIF
78    
79     C- fill in tOceMxL with Sea-Surface Temp. from the ocean component
80 jmc 1.2 IF ( useImportSST ) THEN
81 jmc 1.1 DO j=1,sNy
82     DO i=1,sNx
83     IF ( land_frc(i,j,bi,bj) .LT. 1. ) THEN
84     tOceMxL(i,j,bi,bj) = SSTocn(i,j,bi,bj)
85     ENDIF
86     ENDDO
87     ENDDO
88     ENDIF
89    
90     C- fill in sOceMxL with Sea-Surf Salinity from the ocean component
91 jmc 1.2 IF ( useImportSSS ) THEN
92 jmc 1.1 DO j=1,sNy
93     DO i=1,sNx
94     IF ( land_frc(i,j,bi,bj) .LT. 1. ) THEN
95     sOceMxL(i,j,bi,bj) = SSSocn(i,j,bi,bj)
96     ENDIF
97     ENDDO
98     ENDDO
99     ENDIF
100    
101     C- fill in v2ocMxL with surf. velocity^2 from the ocean component
102 jmc 1.2 IF ( useImportVsq ) THEN
103 jmc 1.1 DO j=1,sNy
104     DO i=1,sNx
105     IF ( land_frc(i,j,bi,bj) .LT. 1. ) THEN
106     v2ocMxL(i,j,bi,bj) = vSqocn(i,j,bi,bj)
107     ENDIF
108     ENDDO
109     ENDDO
110     ENDIF
111    
112 jmc 1.2 ELSEIF ( useAtm_Phys ) THEN
113 jmc 1.1 #else
114 jmc 1.2 IF ( useAtm_Phys ) THEN
115 jmc 1.1 #endif /* ALLOW_THSICE */
116 jmc 1.2 C-- supply imported fields to Atm_Phys pkg:
117    
118     IF ( useImportSST ) THEN
119     DO j=1,sNy
120     DO i=1,sNx
121     atmSST(i,j) = SSTocn(i,j,bi,bj)+celsius2K
122     ENDDO
123     ENDDO
124     ENDIF
125    
126     ELSE
127     C-- supply imported fields to AIM (Phys) pkg:
128 jmc 1.1
129     IF ( useImportSST ) THEN
130     DO j=1,sNy
131     DO i=1,sNx
132     IF ( land_frc(i,j,bi,bj) .LT. 1. ) THEN
133    
134     C-- take SST from the ocean compon where Sea-Ice fraction is zero
135 jmc 1.2 IF ( atmSIfrc(i,j).EQ.0. ) THEN
136     atmSST(i,j) = SSTocn(i,j,bi,bj)+celsius2K
137 jmc 1.1 ELSEIF ( SSTocn(i,j,bi,bj).GE. -1. _d 0) THEN
138     C-- take SST from the ocean compon if clearly warmer than freezing
139     C then reset sea-ice fraction
140 jmc 1.2 atmSST(i,j) = SSTocn(i,j,bi,bj)+celsius2K
141     atmSIfrc(i,j) = 0.
142 jmc 1.1 ENDIF
143    
144     ENDIF
145     ENDDO
146     ENDDO
147     ENDIF
148    
149     C-- if useThSIce / else / endif
150     ENDIF
151    
152     #endif /* COMPONENT_MODULE */
153    
154     RETURN
155     END

  ViewVC Help
Powered by ViewVC 1.1.22