/[MITgcm]/MITgcm/pkg/ocn_compon_interf/cpl_exch_configs.F
ViewVC logotype

Diff of /MITgcm/pkg/ocn_compon_interf/cpl_exch_configs.F

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

revision 1.2 by jmc, Thu Dec 24 16:48:30 2009 UTC revision 1.3 by jmc, Mon Dec 2 22:16:19 2013 UTC
# Line 11  C !INTERFACE: Line 11  C !INTERFACE:
11    
12  C !DESCRIPTION:  C !DESCRIPTION:
13  C     *==========================================================*  C     *==========================================================*
14  C     | SUBROUTINE CPL_EXCH_CONFIGS                              |  C     | SUBROUTINE CPL_EXCH_CONFIGS
15  C     | o Controlling routine for initial config exchange between|  C     | o Controlling routine for initial config exchange between
16  C     |   component models and ocean component.                  |  C     |   component models and ocean component.
17  C     | - Oceanic version -                                      |  C     | - Oceanic version -
18  C     *==========================================================*  C     *==========================================================*
19  C     | Controls the import of configuration information         |  C     | Controls the import of configuration information
20  C     | (grid/topography,etc...) from other components and the   |  C     | (grid/topography,etc...) from other components and the
21  C     | export of configuration information from this component. |  C     | export of configuration information from this component.
22  C     | The routine does some basic checking on consistency      |  C     | The routine does some basic checking on consistency
23  C     | components and summarizes the information that has been  |  C     | components and summarizes the information that has been
24  C     | imported.                                                |  C     | imported.
25  C     | The routine will need to be customised for different     |  C     | The routine will need to be customised for different
26  C     | styles of coupled run. The coupler requires consistency  |  C     | styles of coupled run. The coupler requires consistency
27  C     | between sending and receiving operations posted by       |  C     | between sending and receiving operations posted by
28  C     | various components. Therefore changes in one component   |  C     | various components. Therefore changes in one component
29  C     | model CPL_EXCH_CONFIG may require changes in other       |  C     | model CPL_EXCH_CONFIG may require changes in other
30  C     | component models CPL_EXCH_CONFIG routines as well        |  C     | component models CPL_EXCH_CONFIG routines as well
31  C     | as in the CPL_MASTER_EXCH_CONFIG routine.                |  C     | as in the coupler EXCH_COMPONENT_CONFIG routine.
32  C     *==========================================================*  C     *==========================================================*
33    
34  C !USES:  C !USES:
# Line 36  C !USES: Line 36  C !USES:
36  C     == Global variables ==  C     == Global variables ==
37  #include "SIZE.h"  #include "SIZE.h"
38  #include "EEPARAMS.h"  #include "EEPARAMS.h"
39    #include "PARAMS.h"
40  #include "GRID.h"  #include "GRID.h"
41  #include "OCNCPL.h"  #include "OCNCPL.h"
42    
43  C !INPUT/OUTPUT PARAMETERS:  C !INPUT/OUTPUT PARAMETERS:
 C     == Routine arguments ==  
44  C     myThid :: Thread number for this instance of the routine  C     myThid :: Thread number for this instance of the routine
45        INTEGER myThid        INTEGER myThid
 CEOP  
46    
47  C     == Local variables ==  C !LOCAL VARIABLES:
48        INTEGER I,J,K,bi,bj        INTEGER i, j, bi, bj
49        INTEGER iDiff        LOGICAL errFlag
50        INTEGER jDiff        CHARACTER*70 errMsg
       INTEGER biDiff  
       INTEGER bjDiff  
51        CHARACTER*(MAX_LEN_MBUF) msgBuf        CHARACTER*(MAX_LEN_MBUF) msgBuf
52        _RL seaSurface_ocn        _RL atm_waterOnly, atm_landOnly, depth_noWater
53        _RL groundLevel_atm  CEOP
54    
55  C     Post my configuration information to the coupler "layer".  C     Post my configuration information to the coupler "layer".
56        CALL OCN_EXPORT_OCNCONFIG( myThid )        CALL OCN_EXPORT_OCNCONFIG( myThid )
# Line 65  C     o Get atmospheric model configurat Line 62  C     o Get atmospheric model configurat
62    
63  C     Summarise fields that were imported.  C     Summarise fields that were imported.
64  C     o Plot atmosphere orography  C     o Plot atmosphere orography
65        CALL PLOT_FIELD_XYRL( Hatm,        IF ( debugLevel.GE.debLevB ) THEN
66       &                      'Atmosphere orography on ocean grid',          CALL WRITE_FLD_XY_RL( 'Atm_Land', ' ', landMask, 0, myThid )
67       &                      1, myThid )        ENDIF
68          IF ( debugLevel.GE.debLevC ) THEN
69            CALL PLOT_FIELD_XYRL( landMask,
70         &                  'Atmosphere land/sea mask on ocean grid',
71         &                  1, myThid )
72          ENDIF
73    
74  C     Do consistency checks on imported fields.  C     Do consistency checks on imported fields.
75  C     o Check that atmos. depth is equal to sea-level for all ocean points.  C     o Check that:
76  C       Wherever there is ocean check the atmos extends to the sea-surface.  C      a) where land/sea mask is "water-only", this should be a wet ocean pts
77        iDiff  = 0  C      b) where land/sea mask has "no water",  this should be a dry ocean pts
78        jDiff  = 0        _BARRIER
79        biDiff = 0        _BEGIN_MASTER( myThid )
80        bjDiff = 0        errFlag = .FALSE.
81        seaSurface_ocn  = 0. _d 0        atm_waterOnly = 0. _d 0
82        groundLevel_atm = 1. _d 5        atm_landOnly  = 1. _d 0
83        DO bj=myByLo(myTHid),myByHi(myThid)        depth_noWater = 0. _d 0
84         DO bi=myBxLo(myThid),myBxHi(myThid)        DO bj=1,nSy
85          DO J=1,sNy         DO bi=1,nSx
86           DO I=1,sNx          DO j=1,sNy
87            IF ( R_low(I,J,bi,bj) .NE. seaSurface_ocn .AND.           DO i=1,sNx
88       &          Hatm(I,J,bi,bj) .NE. groundLevel_atm ) THEN            IF ( ( landMask(i,j,bi,bj) .EQ. atm_waterOnly
89             iDiff  = I       &        .AND. R_low(i,j,bi,bj) .EQ. depth_noWater )
90             jDiff  = J       &    .OR. ( landMask(i,j,bi,bj) .EQ. atm_landOnly
91             biDiff = bi       &        .AND. R_low(i,j,bi,bj) .NE. depth_noWater ) ) THEN
92             bjDiff = bj             errFlag = .TRUE.
93             WRITE(msgBuf,'(A,I4,A,I4,A,I4,A,I4,A)')             WRITE(msgBuf,'(2(A,I6),2(A,I4),A)')
94       &     'Inconsistent land/sea mask @ (i=',iDiff,       &     'Inconsistent land/sea mask @ (i=', i, ',j=', j,
95       &     ',j=',jDiff,',bi=',biDiff,',bj=',bjDiff,')'       &                              ',bi=', bi, ',bj=', bj, ')'
96             CALL PRINT_ERROR( msgBuf, myThid )             CALL PRINT_ERROR( msgBuf, myThid )
97             WRITE(msgBuf,'(A,E30.15)')             WRITE(msgBuf,'(A,E30.15)')
98       &     'H (atmosphere) ==',Hatm(I,J,bi,bj)       &     'Land (atmosphere) ==', landMask(i,j,bi,bj)
99             CALL PRINT_ERROR( msgBuf, myThid )             CALL PRINT_ERROR( msgBuf, myThid )
100             WRITE(msgBuf,'(A,E30.15)')             WRITE(msgBuf,'(A,E30.15)')
101       &     'H (ocean)      ==',R_low(I,J,bi,bj)       &     'Depth (ocean)     ==', R_low(i,j,bi,bj)
102             CALL PRINT_ERROR( msgBuf, myThid )             CALL PRINT_ERROR( msgBuf, myThid )
103            ENDIF            ENDIF
104           ENDDO           ENDDO
# Line 104  C       Wherever there is ocean check th Line 106  C       Wherever there is ocean check th
106         ENDDO         ENDDO
107        ENDDO        ENDDO
108    
109        IF ( iDiff .NE. 0 ) THEN        errMsg  = ' '
110  C      At least one point had land/sea "inconsistency" between atmos.        IF ( errFlag ) WRITE(errMsg,'(A)')
111  C      and ocean. Stop if this happens.       &   'OCN_EXCH_CONFIGS: Atm & Oce Land/Sea mask are inconsistent'
112  Ccnh       STOP 'ABNORMAL END: S/R OCN_EXCH_CONFIGS'  
113        ENDIF  C--   All procs in World check for error and stop if any
114          CALL MITCPLR_ALL_CHECK( errFlag, errMsg )
115    
116          _END_MASTER( myThid )
117          _BARRIER
118    
119        RETURN        RETURN
120        END        END

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

  ViewVC Help
Powered by ViewVC 1.1.22