/[MITgcm]/MITgcm/pkg/aim_v23/aim_sice2aim.F
ViewVC logotype

Contents of /MITgcm/pkg/aim_v23/aim_sice2aim.F

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


Revision 1.5 - (show annotations) (download)
Wed Aug 10 20:38:34 2005 UTC (18 years, 9 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint57t_post, checkpoint57v_post, checkpoint57s_post, checkpoint57y_post, checkpoint57y_pre, checkpoint57r_post, checkpoint58, checkpoint57x_post, checkpoint57w_post, checkpint57u_post, checkpoint58a_post, checkpoint57q_post, checkpoint57z_post
Changes since 1.4: +3 -1 lines
forgot to add this line in the previous check-in

1 C $Header: /u/gcmpack/MITgcm/pkg/aim_v23/aim_sice2aim.F,v 1.4 2005/08/09 22:37:08 jmc Exp $
2 C $Name: $
3
4 #include "AIM_OPTIONS.h"
5 #ifdef ALLOW_THSICE
6 #include "THSICE_OPTIONS.h"
7 #endif
8
9 CBOP
10 C !ROUTINE: AIM_SICE2AIM
11 C !INTERFACE:
12 SUBROUTINE AIM_SICE2AIM(
13 I land_frc,
14 U aimTsoce, aimSIfrc,
15 O aimTsice, aimAlb,
16 I myTime, myIter, bi, bj, myThid )
17
18 C !DESCRIPTION: \bv
19 C *================================================================*
20 C | S/R AIM_SICE2AIM
21 C | provide surface Boundary Conditions over sea-ice
22 C | (from thsice pkg) to atmospheric physics package AIM
23 C *================================================================*
24 C *================================================================*
25 C \ev
26
27 C !USES:
28 IMPLICIT NONE
29
30 C == Global variables ===
31 C-- size for MITgcm & Physics package :
32 #include "AIM_SIZE.h"
33
34 C-- MITgcm
35 #include "EEPARAMS.h"
36 #include "PARAMS.h"
37
38 C-- Physics package
39 #include "AIM_PARAMS.h"
40 #include "com_forcon.h"
41
42 #ifdef ALLOW_THSICE
43 C-- Sea-Ice package
44 #include "THSICE_SIZE.h"
45 #include "THSICE_PARAMS.h"
46 #include "THSICE_VARS.h"
47 #include "THSICE_TAVE.h"
48 #endif
49
50 #ifdef COMPONENT_MODULE
51 # include "CPL_PARAMS.h"
52 #else
53 LOGICAL cpl_earlyExpImpCall
54 #endif
55
56 C !INPUT/OUTPUT PARAMETERS:
57 C == Routine arguments ==
58 C land_frc :: land fraction [0-1]
59 C aimTsoce :: sea surface temp [K], used in AIM
60 C aimSIfrc :: sea-ice fraction [0-1]
61 C aimTsice :: sea-ice (or snow) surface temp (K), used in AIM
62 C aimAlb :: sea-ice albedo [0-1], used in AIM
63 C myTime :: Current time of simulation ( s )
64 C myIter :: Current iteration number in simulation
65 C bi,bj :: Tile index
66 C myThid :: Number of this instance of the routine
67 _RS land_frc(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
68 _RL aimTsoce(sNx,sNy)
69 _RL aimSIfrc(sNx,sNy)
70 _RL aimTsice(sNx,sNy)
71 _RL aimAlb(sNx,sNy)
72 INTEGER myIter, bi, bj, myThid
73 _RL myTime
74 CEOP
75
76 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
77
78 #ifdef ALLOW_AIM
79 #ifdef ALLOW_THSICE
80
81 C == Local variables ==
82 C i,j :: Loop counters
83 INTEGER i,j
84
85 IF ( .TRUE. ) THEN
86 C- Use thsice-pkg output instead of prescribed Temp & ice fraction
87 DO j=1,sNy
88 DO i=1,sNx
89 aimTsice(i,j) = Tsrf(i,j,bi,bj)+celsius2K
90 aimSIfrc(i,j) = iceMask(i,j,bi,bj)
91 ENDDO
92 ENDDO
93 ELSE
94 C- Fill in thsice-pkg Temp. using AIM surf. fields
95 DO j=1,sNy
96 DO i=1,sNx
97 Tsrf (i,j,bi,bj) = aimTsice(i,j)-celsius2K
98 Tice1(i,j,bi,bj) = Tsrf (i,j,bi,bj)
99 Tice2(i,j,bi,bj) = Tsrf (i,j,bi,bj)
100 iceMask(i,j,bi,bj) = aimSIfrc(i,j)
101 ENDDO
102 ENDDO
103 ENDIF
104
105 IF ( .TRUE. ) THEN
106 C- Compute albedo over sea-ice
107 DO j=1,sNy
108 DO i=1,sNx
109 IF ( iceMask(i,j,bi,bj) .GT. 0. _d 0 ) THEN
110 CALL THSICE_ALBEDO(
111 I snowHeight(i,j,bi,bj), iceHeight(i,j,bi,bj),
112 I Tsrf(i,j,bi,bj), snowAge(i,j,bi,bj),
113 O aimAlb(i,j),
114 I myThid)
115 ELSE
116 aimAlb(i,j) = ALBICE
117 ENDIF
118 siceAlb(i,j,bi,bj) = iceMask(i,j,bi,bj)*aimAlb(i,j)
119 ENDDO
120 ENDDO
121 ELSE
122 C- Surface Albedo : (from F.M. FORDATE S/R)
123 DO j=1,sNy
124 DO i=1,sNx
125 aimAlb(i,j) = ALBICE
126 ENDDO
127 ENDDO
128 ENDIF
129
130 C-- fill in ocean mixed layer variables
131 C notes: this replace reading initial conditions from files.
132 C needs to be done before call to phy_driver (since freezing
133 C temp. is fct of salinity) ; but would be better somewhere else.
134 IF ( tauRelax_MxL .EQ. -1. _d 0
135 & .OR. ( stepFwd_oceMxL .AND. StartIceModel.NE.0
136 & .AND. myIter.EQ.nIter0 )
137 & .OR. ( myIter.EQ.0 .AND. myTime.EQ.baseTime .AND.
138 & .NOT.(useCoupler.AND.cpl_earlyExpImpCall) )
139 & ) THEN
140 DO j=1,sNy
141 DO i=1,sNx
142 IF ( land_frc(i,j,bi,bj) .LT. 1. _d 0 ) THEN
143 tOceMxL(i,j,bi,bj) = aimTsoce(i,j)-celsius2K
144 sOceMxL(i,j,bi,bj) = sMxL_default
145 ENDIF
146 ENDDO
147 ENDDO
148 ELSE
149 C-- Use ocean mixed layer Temp as Atmos. SST (instead of prescribed Temp)
150 DO j=1,sNy
151 DO i=1,sNx
152 IF ( land_frc(i,j,bi,bj) .LT. 1. _d 0 ) THEN
153 aimTsoce(i,j) = tOceMxL(i,j,bi,bj)+celsius2K
154 ENDIF
155 ENDDO
156 ENDDO
157 ENDIF
158
159 #endif /* ALLOW_THSICE */
160 #endif /* ALLOW_AIM */
161
162 RETURN
163 END

  ViewVC Help
Powered by ViewVC 1.1.22