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

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

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


Revision 1.10 - (show annotations) (download)
Thu Jun 30 23:09:08 2005 UTC (18 years, 11 months ago) by molod
Branch: MAIN
CVS Tags: checkpoint57m_post, checkpoint57r_post, checkpoint57n_post, checkpoint57l_post, checkpoint57p_post, checkpoint57q_post, checkpoint57o_post, checkpoint57k_post
Changes since 1.9: +7 -1 lines
Handling of diagnostics in fizhi and aim adjusted - fizhi inits it own diagnostics,
                                                    aim too (no more atm common diag init)

1 C $Header: /u/gcmpack/MITgcm/pkg/aim_v23/aim_initialise.F,v 1.9 2005/06/23 20:02:50 edhill Exp $
2 C $Name: $
3
4 #include "AIM_OPTIONS.h"
5
6 SUBROUTINE AIM_INITIALISE( myThid )
7 C *==================================================================*
8 C | S/R AIM_INITIALISE
9 C *==================================================================*
10 C | Initialisation of AIM atmospheric physics package :
11 C | 1) call iniphys (=> set parameters to default value)
12 C | 2) read AIM parameters
13 C *==================================================================*
14 IMPLICIT NONE
15
16 C -------------- Global variables ------------------------------------
17 #include "SIZE.h"
18 #include "EEPARAMS.h"
19 #include "PARAMS.h"
20 #include "GRID.h"
21 #include "SURFACE.h"
22 #include "DYNVARS.h"
23 #include "AIM_PARAMS.h"
24 #include "AIM_FFIELDS.h"
25 c #include "AIM_GRID.h"
26 #include "AIM_DIAGS.h"
27 #ifdef ALLOW_MNC
28 #include "MNC_PARAMS.h"
29 #endif
30
31 C == Routine arguments ==
32 C myThid - Number of this instance
33 INTEGER myThid
34
35 #ifdef ALLOW_AIM
36 C == Local variables ==
37 C HSG - Cell face in vertical
38 C pGround - Lower boundary pressure
39 C i, j, k, bi,bj - Loop counters
40 _RL HSG(0:Nr)
41 _RL pGround, tmpPgrnd
42 INTEGER i, j, K, bi, bj
43 INTEGER Katm
44
45 C-- Set default value for AIM interface code (AIM_PARAMS.h):
46 aim_useFMsurfBC = .TRUE.
47 aim_useMMsurfFc = .FALSE.
48 aim_surfPotTemp = .FALSE.
49 aim_energPrecip = .FALSE.
50 aim_splitSIOsFx = .FALSE.
51 aim_clrSkyDiag = .FALSE.
52 aim_tave_mdsio = .TRUE.
53 #ifdef ALLOW_MNC
54 aim_tave_mnc = timeave_mnc
55 #else
56 aim_tave_mnc = .FALSE.
57 #endif
58 aim_MMsufx = '.bin'
59 aim_MMsufxLength = 4
60 aim_LandFile = ' '
61 aim_albFile = ' '
62 aim_vegFile = ' '
63 aim_sstFile = ' '
64 aim_lstFile = ' '
65 aim_oiceFile = ' '
66 aim_snowFile = ' '
67 aim_swcFile = ' '
68 aim_dragStrato = 0.
69 aim_taveFreq = taveFreq
70 aim_diagFreq = dumpFreq
71 aim_tendFreq = 0.
72
73 C-- Set default value for atmos. physics parameters:
74 pGround = atm_Po
75 DO k=1,Nr
76 Katm = _KD2KA( k )
77 HSG(Katm) = rF(k)/pGround
78 ENDDO
79 k=Nr+1
80 Katm = _KD2KA( k )
81 HSG(Katm) = rF(k)/pGround
82
83 c DO bj = myByLo(myThid), myByHi(myThid)
84 c DO bi = myBxLo(myThid), myBxHi(myThid)
85
86 C-- set default value for all atmos. physics parameter:
87 CALL INPHYS( HSG, myThid )
88
89 c ENDDO
90 c ENDDO
91
92 C-- Read AIM parameters (from file data.aimphys):
93 CALL AIM_READPARMS( myThid )
94
95 C-- set energy fractions in LW bands as a function of temperature:
96 C initialize common block RADFIX (originally called from FORDATE in SPEEDY)
97 _BEGIN_MASTER(myThid)
98 CALL RADSET( myThid)
99 _END_MASTER ( myThid)
100
101 C-- Set truncSurfP : used to correct for truncation (because of hFacMin)
102 C of surface reference pressure Ro_surf that affects Surf.Temp.
103 CALL INI_P_GROUND(1, topoZ, truncSurfP, myThid )
104 DO bj = myByLo(myThid), myByHi(myThid)
105 DO bi = myBxLo(myThid), myBxHi(myThid)
106 DO j=1,sNy
107 DO i=1,sNx
108 tmpPgrnd = MIN(truncSurfP(i,j,bi,bj),atm_Po)
109 truncSurfP(i,j,bi,bj)=
110 & ( Ro_surf(i,j,bi,bj)/tmpPgrnd )**atm_kappa
111 ENDDO
112 ENDDO
113 IF (aim_useMMsurfFc .AND. aim_surfPotTemp) THEN
114 DO j=1,sNy
115 DO i=1,sNx
116 truncSurfP(i,j,bi,bj) =
117 & ( Ro_surf(i,j,bi,bj)/atm_Po )**atm_kappa
118 ENDDO
119 ENDDO
120 ENDIF
121 ENDDO
122 ENDDO
123
124 C-- Initialise Land Fraction (in AIM_FFIELDS.h):
125 DO bj = myByLo(myThid), myByHi(myThid)
126 DO bi = myBxLo(myThid), myBxHi(myThid)
127 DO j=1-Oly,sNy+Oly
128 DO i=1-Olx,sNx+Olx
129 aim_landFr (i,j,bi,bj) = 0.
130 ENDDO
131 ENDDO
132 ENDDO
133 ENDDO
134
135 IF ( aim_LandFile .NE. ' ' ) THEN
136 CALL READ_REC_XY_RS(aim_LandFile,aim_landFr,1,nIter0,myThid)
137 ENDIF
138
139 #ifdef ALLOW_MNC
140 IF (useMNC) THEN
141 CALL AIM_MNC_INIT( myThid )
142 ENDIF
143 #endif /* ALLOW_MNC */
144
145 #ifdef ALLOW_DIAGNOSTICS
146 if ( useDiagnostics ) then
147 call aim_diagnostics_init( myThid )
148 endif
149 #endif
150
151 #endif /* ALLOW_AIM */
152
153 RETURN
154 END

  ViewVC Help
Powered by ViewVC 1.1.22