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

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

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


Revision 1.3 - (hide annotations) (download)
Fri Jan 3 03:51:27 2003 UTC (21 years, 4 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint48e_post, checkpoint48b_post, checkpoint48c_pre, checkpoint48d_pre, checkpoint47i_post, checkpoint48d_post, checkpoint48f_post, checkpoint47g_post, checkpoint48a_post, checkpoint47j_post, checkpoint48c_post, checkpoint48, checkpoint47h_post, checkpoint48g_post
Changes since 1.2: +17 -7 lines
 time-average AIM output: become independent from statvars time-average
  (can be used with #undef ALLOW_TIMEAVE) ; add new variables (e.g., RH)

1 jmc 1.3 C $Header: /u/gcmpack/MITgcm/pkg/aim_v23/aim_initialise.F,v 1.2 2002/12/10 02:35:27 jmc Exp $
2 jmc 1.1 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 | 3) initialisation of AIM arrays (time-ave)
14     C *==================================================================*
15     IMPLICIT NONE
16    
17     C -------------- Global variables ------------------------------------
18     #include "SIZE.h"
19     #include "EEPARAMS.h"
20     #include "PARAMS.h"
21 jmc 1.2 #include "GRID.h"
22     #include "SURFACE.h"
23 jmc 1.1 #include "DYNVARS.h"
24 jmc 1.2 #include "AIM_PARAMS.h"
25     #include "AIM_FFIELDS.h"
26     c #include "AIM_GRID.h"
27 jmc 1.1 #include "AIM_DIAGS.h"
28    
29     C == Routine arguments ==
30     C myThid - Number of this instance
31     INTEGER myThid
32    
33     #ifdef ALLOW_AIM
34     C == Local variables ==
35     C HSG - Cell face in vertical
36     C pGround - Lower boundary pressure
37 jmc 1.2 C i, j, k, bi,bj - Loop counters
38 jmc 1.1 _RL HSG(0:Nr)
39 jmc 1.2 _RL pGround, tmpPgrnd
40     INTEGER i, j, K, bi, bj
41 jmc 1.1 INTEGER Katm
42    
43 jmc 1.2 C-- Set default value for AIM interface code (AIM_PARAMS.h):
44     aim_useFMsurfBC = .TRUE.
45     aim_useMMsurfFc = .FALSE.
46     aim_surfPotTemp = .FALSE.
47     aim_MMsufx = '.bin'
48     aim_MMsufxLength = 4
49     aim_LandFile = ' '
50     aim_albFile = ' '
51     aim_vegFile = ' '
52     aim_sstFile = ' '
53     aim_lstFile = ' '
54     aim_oiceFile = ' '
55     aim_snowFile = ' '
56     aim_swcFile = ' '
57 jmc 1.3 aim_taveFreq = taveFreq
58 jmc 1.2 aim_diagFreq = dumpFreq
59     aim_tendFreq = 0.
60    
61     C-- Set default value for atmos. physics parameters:
62     pGround = atm_Po
63     DO k=1,Nr
64     Katm = _KD2KA( k )
65     HSG(Katm) = rF(k)/pGround
66 jmc 1.1 ENDDO
67 jmc 1.2 k=Nr+1
68     Katm = _KD2KA( k )
69     HSG(Katm) = rF(k)/pGround
70 jmc 1.1
71     c DO bj = myByLo(myThid), myByHi(myThid)
72     c DO bi = myBxLo(myThid), myBxHi(myThid)
73    
74     C-- set default value for all atmos. physics parameter:
75     CALL INPHYS( HSG, myThid )
76    
77     c ENDDO
78     c ENDDO
79    
80 jmc 1.2 C-- Read AIM parameters (from file data.aimphys):
81     CALL AIM_READPARMS( myThid )
82    
83 jmc 1.1 C-- set energy fractions in LW bands as a function of temperature:
84     C initialize common block RADFIX (originally called from FORDATE in SPEEDY)
85     _BEGIN_MASTER(myThid)
86     CALL RADSET( myThid)
87     _END_MASTER ( myThid)
88    
89 jmc 1.2 C-- Set truncSurfP : used to correct for truncation (because of hFacMin)
90     C of surface reference pressure Ro_surf that affects Surf.Temp.
91     CALL INI_P_GROUND(selectFindRoSurf, topoZ, truncSurfP, myThid )
92     DO bj = myByLo(myThid), myByHi(myThid)
93     DO bi = myBxLo(myThid), myBxHi(myThid)
94     DO j=1,sNy
95     DO i=1,sNx
96     tmpPgrnd = MIN(truncSurfP(i,j,bi,bj),atm_Po)
97     truncSurfP(i,j,bi,bj)=
98     & ( Ro_surf(i,j,bi,bj)/tmpPgrnd )**atm_kappa
99     ENDDO
100     ENDDO
101     IF (aim_useMMsurfFc .AND. aim_surfPotTemp) THEN
102     DO j=1,sNy
103     DO i=1,sNx
104     truncSurfP(i,j,bi,bj) =
105     & ( Ro_surf(i,j,bi,bj)/atm_Po )**atm_kappa
106     ENDDO
107     ENDDO
108     ENDIF
109     ENDDO
110     ENDDO
111    
112     C-- Initialise surface forcing fields (in AIM_FFIELDS.h):
113     c DO bj = myByLo(myThid), myByHi(myThid)
114     c DO bi = myBxLo(myThid), myBxHi(myThid)
115     c DO j=1-Oly,sNy+Oly
116     c DO i=1-Olx,sNx+Olx
117     c aim_surfTemp(i,j,bi,bj) = 300.
118     c aim_soilWater(i,j,bi,bj) = 0.
119     c aim_albedo (i,j,bi,bj) = 0.
120     c aim_landFr (i,j,bi,bj) = 0.
121     c ENDDO
122     c ENDDO
123     c ENDDO
124     c ENDDO
125 jmc 1.1
126 jmc 1.3 #ifdef ALLOW_AIM_TAVE
127 jmc 1.1 C Initialise diagnostic counters (these are cleared on model start
128     C i.e. not loaded from history file for now ).
129     DO bj = myByLo(myThid), myByHi(myThid)
130     DO bi = myBxLo(myThid), myBxHi(myThid)
131     CALL TIMEAVE_RESET(USTRtave, 1, bi, bj, myThid)
132     CALL TIMEAVE_RESET(VSTRtave, 1, bi, bj, myThid)
133     CALL TIMEAVE_RESET(TSRtave, 1, bi, bj, myThid)
134     CALL TIMEAVE_RESET(OLRtave, 1, bi, bj, myThid)
135     CALL TIMEAVE_RESET(SSRtave, 1, bi, bj, myThid)
136     CALL TIMEAVE_RESET(SLRtave, 1, bi, bj, myThid)
137     CALL TIMEAVE_RESET(SHFtave, 1, bi, bj, myThid)
138     CALL TIMEAVE_RESET(EVAPtave, 1, bi, bj, myThid)
139 jmc 1.3 CALL TIMEAVE_RESET(PRECNVtave,1, bi, bj, myThid)
140     CALL TIMEAVE_RESET(PRECLStave,1, bi, bj, myThid)
141     CALL TIMEAVE_RESET(CLOUDCtave,1, bi, bj, myThid)
142     CALL TIMEAVE_RESET(CLTOPtave, 1, bi, bj, myThid)
143     CALL TIMEAVE_RESET(CBMFtave, 1, bi, bj, myThid)
144     CALL TIMEAVE_RESET(DRAGtave, 1, bi, bj, myThid)
145     CALL TIMEAVE_RESET(aimV0tave, 1, bi, bj, myThid)
146     CALL TIMEAVE_RESET(aimT0tave, 1, bi, bj, myThid)
147     CALL TIMEAVE_RESET(aimQ0tave, 1, bi, bj, myThid)
148     CALL TIMEAVE_RESET(aimRHtave,Nr, bi, bj, myThid)
149     DO k=1,Nr
150     aim_timeAve(k,bi,bj) = 0.
151     ENDDO
152 jmc 1.1 ENDDO
153     ENDDO
154 jmc 1.3 #endif /* ALLOW_AIM_TAVE */
155 jmc 1.1
156     #endif /* ALLOW_AIM */
157    
158     RETURN
159     END

  ViewVC Help
Powered by ViewVC 1.1.22