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

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

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

revision 1.3 by jmc, Fri Jan 3 03:51:27 2003 UTC revision 1.11 by edhill, Sun Sep 11 04:35:31 2005 UTC
# Line 10  C     *================================= Line 10  C     *=================================
10  C     | Initialisation of AIM atmospheric physics package :  C     | Initialisation of AIM atmospheric physics package :
11  C     | 1) call iniphys (=> set parameters to default value)  C     | 1) call iniphys (=> set parameters to default value)
12  C     | 2) read AIM parameters  C     | 2) read AIM parameters
 C     | 3) initialisation of AIM arrays (time-ave)  
13  C     *==================================================================*  C     *==================================================================*
14        IMPLICIT NONE        IMPLICIT NONE
15    
# Line 25  C     -------------- Global variables -- Line 24  C     -------------- Global variables --
24  #include "AIM_FFIELDS.h"  #include "AIM_FFIELDS.h"
25  c #include "AIM_GRID.h"  c #include "AIM_GRID.h"
26  #include "AIM_DIAGS.h"  #include "AIM_DIAGS.h"
27    #ifdef ALLOW_MNC
28    #include "MNC_PARAMS.h"
29    #endif
30    
31  C     == Routine arguments ==  C     == Routine arguments ==
32  C     myThid -  Number of this instance  C     myThid -  Number of this instance
# Line 44  C--  Set default value for AIM interface Line 46  C--  Set default value for AIM interface
46        aim_useFMsurfBC = .TRUE.        aim_useFMsurfBC = .TRUE.
47        aim_useMMsurfFc = .FALSE.        aim_useMMsurfFc = .FALSE.
48        aim_surfPotTemp = .FALSE.        aim_surfPotTemp = .FALSE.
49          aim_energPrecip = .FALSE.
50          aim_splitSIOsFx = .FALSE.
51          aim_clrSkyDiag  = .FALSE.
52    #ifdef ALLOW_MNC
53          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    #else
58          aim_timeave_mnc       = .FALSE.
59          aim_snapshot_mnc      = .FALSE.
60          aim_pickup_write_mnc  = .FALSE.
61          aim_pickup_read_mnc   = .FALSE.
62    #endif
63        aim_MMsufx = '.bin'        aim_MMsufx = '.bin'
64        aim_MMsufxLength = 4        aim_MMsufxLength = 4
65        aim_LandFile = ' '        aim_LandFile = ' '
# Line 54  C--  Set default value for AIM interface Line 70  C--  Set default value for AIM interface
70        aim_oiceFile = ' '        aim_oiceFile = ' '
71        aim_snowFile = ' '        aim_snowFile = ' '
72        aim_swcFile  = ' '        aim_swcFile  = ' '
73          aim_dragStrato = 0.
74        aim_taveFreq = taveFreq        aim_taveFreq = taveFreq
75        aim_diagFreq = dumpFreq        aim_diagFreq = dumpFreq
76        aim_tendFreq = 0.        aim_tendFreq = 0.
77          
78  C--  Set default value for atmos. physics parameters:  C--  Set default value for atmos. physics parameters:
79        pGround = atm_Po        pGround = atm_Po
80        DO k=1,Nr        DO k=1,Nr
# Line 88  C     initialize common block RADFIX (or Line 105  C     initialize common block RADFIX (or
105    
106  C--   Set truncSurfP : used to correct for truncation (because of hFacMin)  C--   Set truncSurfP : used to correct for truncation (because of hFacMin)
107  C      of surface reference pressure Ro_surf that affects Surf.Temp.  C      of surface reference pressure Ro_surf that affects Surf.Temp.
108        CALL INI_P_GROUND(selectFindRoSurf, topoZ, truncSurfP, myThid )        CALL INI_P_GROUND(1, topoZ, truncSurfP, myThid )
109        DO bj = myByLo(myThid), myByHi(myThid)        DO bj = myByLo(myThid), myByHi(myThid)
110         DO bi = myBxLo(myThid), myBxHi(myThid)         DO bi = myBxLo(myThid), myBxHi(myThid)
111          DO j=1,sNy          DO j=1,sNy
# Line 109  C      of surface reference pressure Ro_ Line 126  C      of surface reference pressure Ro_
126         ENDDO         ENDDO
127        ENDDO        ENDDO
128                
129  C--   Initialise surface forcing fields (in AIM_FFIELDS.h):  C--   Initialise Land Fraction (in AIM_FFIELDS.h):
 c     DO bj = myByLo(myThid), myByHi(myThid)  
 c      DO bi = myBxLo(myThid), myBxHi(myThid)  
 c       DO j=1-Oly,sNy+Oly  
 c        DO i=1-Olx,sNx+Olx    
 c         aim_surfTemp(i,j,bi,bj) = 300.  
 c         aim_soilWater(i,j,bi,bj) = 0.  
 c         aim_albedo   (i,j,bi,bj) = 0.  
 c         aim_landFr   (i,j,bi,bj) = 0.  
 c        ENDDO  
 c       ENDDO  
 c      ENDDO  
 c     ENDDO  
   
 #ifdef ALLOW_AIM_TAVE  
 C     Initialise diagnostic counters (these are cleared on model start  
 C      i.e. not loaded from history file for now ).  
130        DO bj = myByLo(myThid), myByHi(myThid)        DO bj = myByLo(myThid), myByHi(myThid)
131         DO bi = myBxLo(myThid), myBxHi(myThid)         DO bi = myBxLo(myThid), myBxHi(myThid)
132          CALL TIMEAVE_RESET(USTRtave, 1, bi, bj, myThid)          DO j=1-Oly,sNy+Oly
133          CALL TIMEAVE_RESET(VSTRtave, 1, bi, bj, myThid)           DO i=1-Olx,sNx+Olx  
134          CALL TIMEAVE_RESET(TSRtave, 1, bi, bj, myThid)            aim_landFr   (i,j,bi,bj) = 0.
135          CALL TIMEAVE_RESET(OLRtave, 1, bi, bj, myThid)           ENDDO
         CALL TIMEAVE_RESET(SSRtave, 1, bi, bj, myThid)  
         CALL TIMEAVE_RESET(SLRtave, 1, bi, bj, myThid)  
         CALL TIMEAVE_RESET(SHFtave, 1, bi, bj, myThid)  
         CALL TIMEAVE_RESET(EVAPtave, 1, bi, bj, myThid)  
         CALL TIMEAVE_RESET(PRECNVtave,1, bi, bj, myThid)  
         CALL TIMEAVE_RESET(PRECLStave,1, bi, bj, myThid)  
         CALL TIMEAVE_RESET(CLOUDCtave,1, bi, bj, myThid)  
         CALL TIMEAVE_RESET(CLTOPtave, 1, bi, bj, myThid)  
         CALL TIMEAVE_RESET(CBMFtave,  1, bi, bj, myThid)  
         CALL TIMEAVE_RESET(DRAGtave,  1, bi, bj, myThid)  
         CALL TIMEAVE_RESET(aimV0tave, 1, bi, bj, myThid)  
         CALL TIMEAVE_RESET(aimT0tave, 1, bi, bj, myThid)  
         CALL TIMEAVE_RESET(aimQ0tave, 1, bi, bj, myThid)  
         CALL TIMEAVE_RESET(aimRHtave,Nr, bi, bj, myThid)  
         DO k=1,Nr  
           aim_timeAve(k,bi,bj) = 0.  
136          ENDDO          ENDDO
137         ENDDO         ENDDO
138        ENDDO        ENDDO
139  #endif /* ALLOW_AIM_TAVE */  
140          IF ( aim_LandFile .NE. ' '  ) THEN
141             CALL READ_REC_XY_RS(aim_LandFile,aim_landFr,1,nIter0,myThid)
142          ENDIF
143    
144    #ifdef ALLOW_MNC
145          IF (useMNC) THEN
146            CALL AIM_MNC_INIT( myThid )
147          ENDIF
148    #endif /*  ALLOW_MNC  */
149    
150    #ifdef ALLOW_DIAGNOSTICS
151          if ( useDiagnostics ) then
152            call aim_diagnostics_init( myThid )
153          endif
154    #endif
155    
156  #endif /* ALLOW_AIM */  #endif /* ALLOW_AIM */
157    

Legend:
Removed from v.1.3  
changed lines
  Added in v.1.11

  ViewVC Help
Powered by ViewVC 1.1.22