/[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.2 - (hide annotations) (download)
Tue Dec 10 02:35:27 2002 UTC (21 years, 6 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint47e_post, checkpoint47d_pre, checkpoint47d_post, branch-exfmods-tag, checkpoint47f_post
Branch point for: branch-exfmods-curt
Changes since 1.1: +73 -13 lines
allow to use AIM physics with SPEEDY input files (from Franco Molteni):
 surface Boundary-Conditions are computed in (new) S/R aim_surf_bc.F.
can still use monthly mean (NCEP) surface forcing (with surface
 Temperature or surface Pot.Temp)

1 jmc 1.2 C $Header: /u/gcmpack/MITgcm/pkg/aim_v23/aim_initialise.F,v 1.1 2002/11/22 17:17:03 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     aim_diagFreq = dumpFreq
58     aim_tendFreq = 0.
59    
60     C-- Set default value for atmos. physics parameters:
61     pGround = atm_Po
62     DO k=1,Nr
63     Katm = _KD2KA( k )
64     HSG(Katm) = rF(k)/pGround
65 jmc 1.1 ENDDO
66 jmc 1.2 k=Nr+1
67     Katm = _KD2KA( k )
68     HSG(Katm) = rF(k)/pGround
69 jmc 1.1
70     c DO bj = myByLo(myThid), myByHi(myThid)
71     c DO bi = myBxLo(myThid), myBxHi(myThid)
72    
73     C-- set default value for all atmos. physics parameter:
74     CALL INPHYS( HSG, myThid )
75    
76     c ENDDO
77     c ENDDO
78    
79 jmc 1.2 C-- Read AIM parameters (from file data.aimphys):
80     CALL AIM_READPARMS( myThid )
81    
82 jmc 1.1 C-- set energy fractions in LW bands as a function of temperature:
83     C initialize common block RADFIX (originally called from FORDATE in SPEEDY)
84     _BEGIN_MASTER(myThid)
85     CALL RADSET( myThid)
86     _END_MASTER ( myThid)
87    
88 jmc 1.2 C-- Set truncSurfP : used to correct for truncation (because of hFacMin)
89     C of surface reference pressure Ro_surf that affects Surf.Temp.
90     CALL INI_P_GROUND(selectFindRoSurf, topoZ, truncSurfP, myThid )
91     DO bj = myByLo(myThid), myByHi(myThid)
92     DO bi = myBxLo(myThid), myBxHi(myThid)
93     DO j=1,sNy
94     DO i=1,sNx
95     tmpPgrnd = MIN(truncSurfP(i,j,bi,bj),atm_Po)
96     truncSurfP(i,j,bi,bj)=
97     & ( Ro_surf(i,j,bi,bj)/tmpPgrnd )**atm_kappa
98     ENDDO
99     ENDDO
100     IF (aim_useMMsurfFc .AND. aim_surfPotTemp) THEN
101     DO j=1,sNy
102     DO i=1,sNx
103     truncSurfP(i,j,bi,bj) =
104     & ( Ro_surf(i,j,bi,bj)/atm_Po )**atm_kappa
105     ENDDO
106     ENDDO
107     ENDIF
108     ENDDO
109     ENDDO
110    
111     C-- Initialise surface forcing fields (in AIM_FFIELDS.h):
112     c DO bj = myByLo(myThid), myByHi(myThid)
113     c DO bi = myBxLo(myThid), myBxHi(myThid)
114     c DO j=1-Oly,sNy+Oly
115     c DO i=1-Olx,sNx+Olx
116     c aim_surfTemp(i,j,bi,bj) = 300.
117     c aim_soilWater(i,j,bi,bj) = 0.
118     c aim_albedo (i,j,bi,bj) = 0.
119     c aim_landFr (i,j,bi,bj) = 0.
120     c ENDDO
121     c ENDDO
122     c ENDDO
123     c ENDDO
124 jmc 1.1
125     #ifdef ALLOW_TIMEAVE
126     C Initialise diagnostic counters (these are cleared on model start
127     C i.e. not loaded from history file for now ).
128     DO bj = myByLo(myThid), myByHi(myThid)
129     DO bi = myBxLo(myThid), myBxHi(myThid)
130     CALL TIMEAVE_RESET(USTRtave, 1, bi, bj, myThid)
131     CALL TIMEAVE_RESET(VSTRtave, 1, bi, bj, myThid)
132     CALL TIMEAVE_RESET(TSRtave, 1, bi, bj, myThid)
133     CALL TIMEAVE_RESET(OLRtave, 1, bi, bj, myThid)
134     CALL TIMEAVE_RESET(SSRtave, 1, bi, bj, myThid)
135     CALL TIMEAVE_RESET(SLRtave, 1, bi, bj, myThid)
136     CALL TIMEAVE_RESET(SHFtave, 1, bi, bj, myThid)
137     CALL TIMEAVE_RESET(EVAPtave, 1, bi, bj, myThid)
138     CALL TIMEAVE_RESET(PRECNVtave, 1, bi, bj, myThid)
139     CALL TIMEAVE_RESET(PRECLStave, 1, bi, bj, myThid)
140     CALL TIMEAVE_RESET(CLOUDCtave, 1, bi, bj, myThid)
141     AIM_TimeAve(1,bi,bj) = 0.
142     ENDDO
143     ENDDO
144     #endif /* ALLOW_TIMEAVE */
145    
146     #endif /* ALLOW_AIM */
147    
148     RETURN
149     END

  ViewVC Help
Powered by ViewVC 1.1.22