/[MITgcm]/MITgcm/pkg/zonal_filt/zonal_filt_readparms.F
ViewVC logotype

Contents of /MITgcm/pkg/zonal_filt/zonal_filt_readparms.F

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


Revision 1.1.6.2 - (show annotations) (download)
Wed Jul 31 21:26:29 2002 UTC (21 years, 11 months ago) by jmc
Branch: release1
CVS Tags: release1_p13_pre, release1_p13, release1_p8, release1_p9, release1_p6, release1_p7, release1_p12, release1_p10, release1_p11, release1_p16, release1_p17, release1_p14, release1_p15, release1_p12_pre
Branch point for: release1_50yr
Changes since 1.1.6.1: +4 -4 lines
for a WARNING, use PRINT_MESSAGE(errorMessageUnit) instead of PRINT_ERROR

1 C $Header: /u/gcmpack/MITgcm/pkg/zonal_filt/zonal_filt_readparms.F,v 1.1.6.1 2002/02/26 16:04:50 adcroft Exp $
2 C $Name: $
3
4 #include "ZONAL_FILT_OPTIONS.h"
5
6 SUBROUTINE ZONAL_FILT_READPARMS( myThid )
7 C /==========================================================\
8 C | SUBROUTINE ZONAL_FILT_READPARMS |
9 C | o Routine to initialize Zonal Filter (=FFT) parameters |
10 C |==========================================================|
11 C \==========================================================/
12 IMPLICIT NONE
13
14 C === Global variables ===
15 #include "SIZE.h"
16 #include "EEPARAMS.h"
17 #include "PARAMS.h"
18 #include "ZONAL_FILT.h"
19
20 C === Routine arguments ===
21 INTEGER myThid
22
23 #ifdef ALLOW_ZONAL_FILT
24
25 NAMELIST /ZONFILT_PARM01/
26 & zonal_filt_uvStar, zonal_filt_TrStagg,
27 & zonal_filt_lat,
28 & zonal_filt_cospow, zonal_filt_sinpow,
29 & zonal_filt_mode2dx
30
31 C === Local variables ===
32 C msgBuf - Informational/error meesage buffer
33 C iUnit - Work variable for IO unit number
34 CHARACTER*(MAX_LEN_MBUF) msgBuf
35 INTEGER iUnit
36
37 C-- ZONAL_FILT_READPARMS has been called so we know that
38 C the package is active.
39 c ZONFILTisOn=.TRUE.
40
41 _BEGIN_MASTER(myThid)
42
43 WRITE(msgBuf,'(A)')' ZONAL_FILT_READPARMS: opening data.zonfilt'
44 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
45 & SQUEEZE_RIGHT , 1)
46
47 CALL OPEN_COPY_DATA_FILE(
48 I 'data.zonfilt', 'ZONAL_FILT_READPARMS',
49 O iUnit,
50 I myThid )
51
52 C-- Default flags and values for Zonal Filter
53 zonal_filt_uvStar = .TRUE.
54 zonal_filt_TrStagg = .TRUE.
55 zonal_filt_lat = 90.
56 zonal_filt_sinpow = 2
57 zonal_filt_cospow = 2
58 zonal_filt_mode2dx = 0
59
60 C-- Read parameters from open data file
61 READ(UNIT=iUnit,NML=ZONFILT_PARM01)
62
63 WRITE(msgBuf,'(A)')
64 & ' ZONAL_FILT_READPARMS: finished reading data.zonfilt'
65 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
66 & SQUEEZE_RIGHT , 1)
67
68 c write(*,*) 'Shap_funct, nShap_Tr,UV _Phys=',
69 c & Shap_funct, nShapT, nShapUV, nShapTrPhys, nShapUVPhys
70 c write(*,*) 'Shap_Trtau,Shap_uvtau=',Shap_Trtau,Shap_uvtau
71
72 C-- Close the open data file
73 CLOSE(iUnit)
74 _END_MASTER(myThid)
75
76 C-- Everyone else must wait for the parameters to be loaded
77 _BARRIER
78
79 C-- Check the parameters :
80
81 IF ( .NOT.zonal_filt_uvStar ) THEN
82
83 C- Notes: applying the filter at the end of the time step (after SOLVE_FOR_P)
84 C affects the barotropic flow divergence ; this might not be consistent
85 C with some option of the code.
86
87 IF ( rigidLid ) THEN
88 WRITE(msgBuf,'(2A)') 'ZONAL_FILT with rigidLid ',
89 & 'needs zonal_filt_uvStar=.true.'
90 CALL PRINT_ERROR( msgBuf , 1)
91 STOP 'ABNORMAL END: S/R ZONAL_FILT_READPARMS'
92 ELSEIF ( .NOT.exactConserv ) THEN
93 WRITE(msgBuf,'(2A)') 'S/R ZONAL_FILT_READPARMS: WARNING <<< ',
94 & 'applying Filter after SOLVE_FOR_P (zonal_filt_uvStar=FALSE)'
95 CALL PRINT_MESSAGE(msgBuf, errorMessageUnit, SQUEEZE_RIGHT,1)
96 WRITE(msgBuf,'(2A)') 'S/R ZONAL_FILT_READPARMS: WARNING <<< ',
97 & 'requires to recompute Eta after ==> turn on exactConserv !'
98 CALL PRINT_MESSAGE(msgBuf, errorMessageUnit, SQUEEZE_RIGHT,1)
99 ENDIF
100
101 ENDIF
102
103 #endif /* ALLOW_ZONAL_FILT */
104 RETURN
105 END

  ViewVC Help
Powered by ViewVC 1.1.22