/[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.11 - (hide annotations) (download)
Sun Sep 11 04:35:31 2005 UTC (18 years, 9 months ago) by edhill
Branch: MAIN
CVS Tags: checkpoint57s_post, checkpoint58b_post, checkpoint57y_post, checkpoint58, checkpoint58f_post, checkpoint58d_post, checkpoint58a_post, checkpoint57z_post, checkpoint58m_post, checkpoint57t_post, checkpoint57v_post, checkpoint57y_pre, checkpoint58e_post, checkpint57u_post, checkpoint58k_post, checkpoint58l_post, checkpoint58g_post, checkpoint58h_post, checkpoint58j_post, checkpoint57w_post, checkpoint58i_post, checkpoint57x_post, checkpoint58c_post
Changes since 1.10: +9 -4 lines
 o mnc-ify the aim state vars -- requested by Daniel
   - units attributes need to be fleshed out

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

  ViewVC Help
Powered by ViewVC 1.1.22