/[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.2 - (show annotations) (download)
Thu Apr 22 21:45:02 2004 UTC (20 years, 1 month ago) by jmc
Branch: MAIN
CVS Tags: checkpoint52n_post, checkpoint53d_post, checkpoint54a_pre, checkpoint55c_post, checkpoint54e_post, checkpoint54a_post, checkpoint53c_post, checkpoint55d_pre, checkpoint57b_post, checkpoint57c_pre, checkpoint55j_post, checkpoint56b_post, checkpoint55h_post, checkpoint54b_post, checkpoint53b_pre, checkpoint55b_post, checkpoint54d_post, checkpoint56c_post, checkpoint55, checkpoint53a_post, checkpoint57a_post, checkpoint54, checkpoint54f_post, checkpoint53b_post, checkpoint55g_post, checkpoint55f_post, checkpoint57a_pre, checkpoint55i_post, checkpoint57, checkpoint56, checkpoint53, checkpoint53g_post, checkpoint57c_post, checkpoint55e_post, checkpoint53f_post, checkpoint55a_post, checkpoint53d_pre, checkpoint54c_post, checkpoint56a_post, checkpoint55d_post
Changes since 1.1: +17 -5 lines
use Slab-Ocean temperature as BC for Atmospheric Physics.

1 C $Header: /u/gcmpack/MITgcm/pkg/aim_v23/aim_sice2aim.F,v 1.1 2004/04/08 00:14:09 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 C !INPUT/OUTPUT PARAMETERS:
51 C == Routine arguments ==
52 C land_frc :: land fraction [0-1]
53 C aimTsoce :: sea surface temp [K], used in AIM
54 C aimSIfrc :: sea-ice fraction [0-1]
55 C aimTsice :: sea-ice (or snow) surface temp (K), used in AIM
56 C aimAlb :: sea-ice albedo [0-1], used in AIM
57 C myTime :: Current time of simulation ( s )
58 C myIter :: Current iteration number in simulation
59 C bi,bj :: Tile index
60 C myThid :: Number of this instance of the routine
61 _RS land_frc(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
62 _RL aimTsoce(sNx,sNy)
63 _RL aimSIfrc(sNx,sNy)
64 _RL aimTsice(sNx,sNy)
65 _RL aimAlb(sNx,sNy)
66 INTEGER myIter, bi, bj, myThid
67 _RL myTime
68 CEOP
69
70 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
71
72 #ifdef ALLOW_AIM
73 #ifdef ALLOW_THSICE
74
75 C == Local variables ==
76 C i,j :: Loop counters
77 INTEGER i,j
78
79 IF ( .TRUE. ) THEN
80 C- Use thsice-pkg output instead of prescribed Temp & ice fraction
81 DO j=1,sNy
82 DO i=1,sNx
83 aimTsice(i,j) = Tsrf(i,j,bi,bj)+celsius2K
84 aimSIfrc(i,j) = iceMask(i,j,bi,bj)
85 ENDDO
86 ENDDO
87 ELSE
88 C- Fill in thsice-pkg Temp. using AIM surf. fields
89 DO j=1,sNy
90 DO i=1,sNx
91 Tsrf (i,j,bi,bj) = aimTsice(i,j)-celsius2K
92 Tice1(i,j,bi,bj) = Tsrf (i,j,bi,bj)
93 Tice2(i,j,bi,bj) = Tsrf (i,j,bi,bj)
94 iceMask(i,j,bi,bj) = aimSIfrc(i,j)
95 ENDDO
96 ENDDO
97 ENDIF
98
99 IF ( .TRUE. ) THEN
100 C- Compute albedo over sea-ice
101 DO j=1,sNy
102 DO i=1,sNx
103 IF ( iceMask(i,j,bi,bj) .GT. 0. _d 0 ) THEN
104 CALL THSICE_ALBEDO(
105 I snowHeight(i,j,bi,bj), iceHeight(i,j,bi,bj),
106 I Tsrf(i,j,bi,bj), snowAge(i,j,bi,bj),
107 O aimAlb(i,j),
108 I myThid)
109 ELSE
110 aimAlb(i,j) = ALBICE
111 ENDIF
112 #ifdef ALLOW_TIMEAVE
113 ice_albedo_Ave(i,j,bi,bj) = ice_albedo_Ave(i,j,bi,bj)
114 & + iceMask(i,j,bi,bj)*aimAlb(i,j)*thSIce_deltaT
115 #endif /*ALLOW_TIMEAVE*/
116 ENDDO
117 ENDDO
118 ELSE
119 C- Surface Albedo : (from F.M. FORDATE S/R)
120 DO j=1,sNy
121 DO i=1,sNx
122 aimAlb(i,j) = ALBICE
123 ENDDO
124 ENDDO
125 ENDIF
126
127 C-- fill in ocean mixed layer variables
128 C notes: this replace reading initial conditions from files.
129 C needs to be done before call to phy_driver (since freezing
130 C temp. is fct of salinity) ; but would be better somewhere else.
131 IF ( tauRelax_MxL .EQ. -1. _d 0
132 & .OR. ( stepFwd_oceMxL .AND. StartIceModel.NE.0
133 & .AND. myIter.EQ.nIter0 )
134 & .OR. ( myIter.EQ.0 .AND. myTime .EQ. 0. )
135 & ) THEN
136 DO j=1,sNy
137 DO i=1,sNx
138 IF ( land_frc(i,j,bi,bj) .LT. 1. _d 0 ) THEN
139 tOceMxL(i,j,bi,bj) = aimTsoce(i,j)-celsius2K
140 sOceMxL(i,j,bi,bj) = sMxL_default
141 ENDIF
142 ENDDO
143 ENDDO
144 ELSE
145 C-- Use ocean mixed layer Temp as Atmos. SST (instead of prescribed Temp)
146 DO j=1,sNy
147 DO i=1,sNx
148 IF ( land_frc(i,j,bi,bj) .LT. 1. _d 0 ) THEN
149 aimTsoce(i,j) = tOceMxL(i,j,bi,bj)+celsius2K
150 ENDIF
151 ENDDO
152 ENDDO
153 ENDIF
154
155 #endif /* ALLOW_THSICE */
156 #endif /* ALLOW_AIM */
157
158 RETURN
159 END

  ViewVC Help
Powered by ViewVC 1.1.22