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

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

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

revision 1.3 by jmc, Thu Dec 24 16:49:08 2009 UTC revision 1.4 by jmc, Mon Dec 2 22:13:23 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 atmosphere component.             |  C     |   component models and atmosphere component.
17  C     | - Atmospheric version -                                  |  C     | - Atmospheric 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 41  C     == Global variables == Line 41  C     == Global variables ==
41  #include "ATMCPL.h"  #include "ATMCPL.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, mxlD_noWater
53        _RL groundLevel_atm  C--   local variable in common block
54          _RL landMask_loc(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
55          COMMON / CPL_EXCH_CONFIGS_LOC / landMask_loc
56    CEOP
57    
58          errFlag = .FALSE.
59    
60    C     Get configuration information (=land/sea mask) from other pkg
61          CALL ATM_GET_ATMCONFIG(
62         O                        landMask_loc,
63         I                        myThid )
64    
65  C     Post my configuration information to the coupler "layer".  C     Post my configuration information to the coupler "layer".
66        CALL ATM_EXPORT_ATMCONFIG( myThid )        CALL ATM_EXPORT_ATMCONFIG(
67         U                        errFlag,
68         I                        landMask_loc, myThid )
69    
70  C     Import other component model(s) configuration(s) from the  C     Import other component model(s) configuration(s) from the coupler "layer"
 C     coupler "layer".  
71  C     o Get ocean model configuration  C     o Get ocean model configuration
72        CALL ATM_IMPORT_OCNCONFIG( myThid )        CALL ATM_IMPORT_OCNCONFIG( myThid )
73    
74  C     Summarise fields that were imported.  C     Summarise fields that were imported.
75  C     o Plot ocean depths  C     o Plot ocean depths
76        CALL PLOT_FIELD_XYRL( ocMxlD,        IF ( debugLevel.GE.debLevB ) THEN
77       &                      'Ocean mixed-layer depth on atmos grid',          CALL WRITE_FLD_XY_RL( 'Ocn_MxlD', ' ', ocMxlD, 0, myThid )
78       &                      1, myThid )        ENDIF
79          IF ( debugLevel.GE.debLevC ) THEN
80            CALL PLOT_FIELD_XYRL( ocMxlD,
81         &                  'Ocean mixed-layer depth on atmos grid',
82         &                  1, myThid )
83          ENDIF
84    
85  C     Do consistency checks on imported fields.  C     Do consistency checks on imported fields.
86  C     o Check that atmos. depth is equal to sea-level for all ocean points.  C     o Check that:
87  C       The ocean model has depth == 0 wherever there is land. For non-land  C      a) where land/sea mask is "water-only", this should be a wet ocean pts
88  C       point the atmosphere must extend to the sea-surface. Usually the  C      b) where land/sea mask has "no water",  this should be a dry ocean pts
89  C       atmospheres full depth is 10^5 Pa.        _BARRIER
90        iDiff  = 0        _BEGIN_MASTER( myThid )
91        jDiff  = 0        atm_waterOnly = 0. _d 0
92        biDiff = 0        atm_landOnly  = 1. _d 0
93        bjDiff = 0        mxlD_noWater  = 0. _d 0
94        seaSurface_ocn    = 0. _d 0        DO bj=1,nSy
95  c     groundLevel_atm   = 1. _d 5         DO bi=1,nSx
96        groundLevel_atm   = Ro_SeaLevel          DO j=1,sNy
97        DO bj=myByLo(myTHid),myByHi(myThid)           DO i=1,sNx
98         DO bi=myBxLo(myThid),myBxHi(myThid)            IF ( ( landMask_loc(i,j,bi,bj) .EQ. atm_waterOnly
99          DO J=1,sNy       &           .AND. ocMxlD(i,j,bi,bj) .EQ. mxlD_noWater )
100           DO I=1,sNx       &    .OR. ( landMask_loc(i,j,bi,bj) .EQ. atm_landOnly
101            IF (  ocMxlD(I,J,bi,bj) .NE. seaSurface_ocn  .AND.       &           .AND. ocMxlD(i,j,bi,bj) .NE. mxlD_noWater ) ) THEN
102       &         Ro_surf(I,J,bi,bj) .NE. groundLevel_atm ) THEN             errFlag = .TRUE.
103             iDiff  = I             WRITE(msgBuf,'(2(A,I6),2(A,I4),A)')
104             jDiff  = J       &     'Inconsistent land/sea mask @ (i=', i, ',j=', j,
105             biDiff = bi       &                              ',bi=', bi, ',bj=', bj, ')'
            bjDiff = bj  
            WRITE(msgBuf,'(A,I4,A,I4,A,I4,A,I4,A)')  
      &     'Inconsistent land/sea mask @ (i=',iDiff,  
      &     ',j=',jDiff,',bi=',biDiff,',bj=',bjDiff,')'  
106             CALL PRINT_ERROR( msgBuf, myThid )             CALL PRINT_ERROR( msgBuf, myThid )
107             WRITE(msgBuf,'(A,E30.15)')             WRITE(msgBuf,'(A,E30.15)')
108       &     'H (atmosphere) ==',Ro_surf(I,J,bi,bj)       &     'Land (atmosphere) ==', landMask_loc(i,j,bi,bj)
109             CALL PRINT_ERROR( msgBuf, myThid )             CALL PRINT_ERROR( msgBuf, myThid )
110             WRITE(msgBuf,'(A,E30.15)')             WRITE(msgBuf,'(A,E30.15)')
111       &     'H (ocean)      ==',ocMxlD(I,J,bi,bj)       &     'Mxl-Depth (ocean) ==', ocMxlD(i,j,bi,bj)
112             CALL PRINT_ERROR( msgBuf, myThid )             CALL PRINT_ERROR( msgBuf, myThid )
113            ENDIF            ENDIF
114           ENDDO           ENDDO
# Line 108  c     groundLevel_atm   = 1. _d 5 Line 116  c     groundLevel_atm   = 1. _d 5
116         ENDDO         ENDDO
117        ENDDO        ENDDO
118    
119        IF ( iDiff .NE. 0 ) THEN        errMsg  = ' '
120  C      At least one point had land/sea "inconsistency" between atmos.        IF ( errFlag ) WRITE(errMsg,'(A)')
121  C      and ocean. Stop if this happens.       &   'ATM_EXCH_CONFIGS: Oce & Atm configs are inconsistent'
122  Ccnh       STOP 'ABNORMAL END: S/R ATM_EXCH_CONFIGS'  
123        ENDIF  C--   All procs in World check for error and stop if any
124          CALL MITCPLR_ALL_CHECK( errFlag, errMsg )
125    
126          _END_MASTER( myThid )
127          _BARRIER
128    
129        RETURN        RETURN
130        END        END

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

  ViewVC Help
Powered by ViewVC 1.1.22