/[MITgcm]/MITgcm_contrib/nesting_sannino/nest_child/nest_child_check.F
ViewVC logotype

Contents of /MITgcm_contrib/nesting_sannino/nest_child/nest_child_check.F

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


Revision 1.3 - (show annotations) (download)
Mon Nov 29 14:24:14 2010 UTC (14 years, 8 months ago) by jmc
Branch: MAIN
CVS Tags: HEAD
Changes since 1.2: +59 -17 lines
check for consistent number of nesting-steps between parent & child:
 if they agree, set number of nesting-steps in driver accordingly;
 if not, stop cleanly (call MPI_FINALIZE & stop).

1 C $Header: /u/gcmpack/MITgcm_contrib/nesting_sannino/nest_child/nest_child_check.F,v 1.2 2009/10/23 19:44:02 sannino Exp $
2 C $Name: $
3
4 #include "NEST_CHILD_OPTIONS.h"
5
6 CBOP
7 C !ROUTINE: NEST_CHILD_CHECK
8
9 C !INTERFACE:
10 SUBROUTINE NEST_CHILD_CHECK( myThid )
11
12 C !DESCRIPTION:
13 C *==========================================================*
14 C | SUBROUTINE NEST_CHILD_CHECK
15 C | o Validate basic package setup and inter-package
16 C | dependencies.
17 C *==========================================================*
18
19 C !USES:
20 IMPLICIT NONE
21
22 C === Global variables ===
23 #include "SIZE.h"
24 #include "EEPARAMS.h"
25 #include "PARAMS.h"
26 #include "EESUPPORT.h"
27 #include "NEST_CHILD_PARAMS.h"
28
29 C !INPUT/OUTPUT PARAMETERS:
30 C myThid :: my Thread Id number
31 INTEGER myThid
32 CEOP
33
34 C !LOCAL VARIABLES:
35 C msgBuf :: Informational/error message buffer
36 CHARACTER*(MAX_LEN_MBUF) msgBuf
37 INTEGER nNestSteps, checkSteps
38 INTEGER ierr, istatus
39
40 WRITE(msgBuf,'(A)') 'NEST_CHILD_CHECK: #define ALLOW_NEST_CHILD'
41 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
42 & SQUEEZE_RIGHT, myThid )
43
44 _BEGIN_MASTER( myThid )
45
46 C-- Check length of integration between components.
47 C- units: number of nesting-steps (since driver ignores CLD/PAR time steps)
48 nNestSteps = nTimeSteps/3
49 IF ( MOD( nTimeSteps, 3 ).NE.0 ) nNestSteps = -1
50 IF ( mpiMyId.EQ.0 ) THEN
51 C- Send to driver the number of expected nesting-exchanges with driver:
52 CALL MPI_SEND( nNestSteps, 1, MPI_INTEGER,
53 & MSTR_DRV_C(NST_LEV_C), 3000,
54 & MPI_Comm_World, ierr )
55 ENDIF
56
57 C Receive error code (-1) from World-Master if inconsistent nNestSteps
58 C Note: This is not broadcast from MSTR_DRV_C(NST_LEV_C) since everybody
59 C in the World need to catch error, call MPI_FINALIZE & stop.
60 CALL MPI_BCAST( checkSteps, 1, MPI_INTEGER,
61 & 0, MPI_Comm_World, ierr )
62 C- Check for mismatch:
63 IF ( checkSteps .EQ. -1 ) THEN
64 WRITE(msgBuf,'(A,I8)')
65 & 'NEST_CHILD_CHECK: Nb of nesting steps =', nNestSteps
66 CALL PRINT_ERROR( msgBuf, myThid )
67 WRITE(msgBuf,'(A)')
68 & 'NEST_CHILD_CHECK: PARENT nb of steps does NOT match'
69 CALL PRINT_ERROR( msgBuf, myThid )
70 CALL MPI_FINALIZE(ierr)
71 STOP 'ABNORMAL END: S/R NEST_CHILD_CHECK:'
72 ENDIF
73
74 _END_MASTER(myThid)
75
76 C OASIS needs convection turned off (will be packaged later)
77 c IF (cAdjFreq.NE.0. .OR.
78 c & ivdc_kappa.NE.0.) THEN
79 c WRITE(msgBuf,'(A)') 'Some form of convection has been enabled'
80 c CALL PRINT_ERROR( msgBuf , 1)
81 c STOP 'ABNORMAL END: S/R OASIS_CHECK'
82 c ENDIF
83
84 RETURN
85 END

  ViewVC Help
Powered by ViewVC 1.1.22