/[MITgcm]/MITgcm_contrib/darwin2/pkg/darwin/dic_read_pickup.F
ViewVC logotype

Annotation of /MITgcm_contrib/darwin2/pkg/darwin/dic_read_pickup.F

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


Revision 1.1 - (hide annotations) (download)
Wed Apr 13 18:56:24 2011 UTC (14 years, 3 months ago) by jahn
Branch: MAIN
CVS Tags: ctrb_darwin2_ckpt64k_20130723, ctrb_darwin2_ckpt63l_20120405, ctrb_darwin2_ckpt64h_20130528, ctrb_darwin2_ckpt62v_20110413, ctrb_darwin2_ckpt64m_20130820, ctrb_darwin2_ckpt64f_20130405, ctrb_darwin2_ckpt63f_20111201, ctrb_darwin2_ckpt64a_20121116, ctrb_darwin2_ckpt64n_20130826, ctrb_darwin2_ckpt62y_20110526, ctrb_darwin2_ckpt64i_20130622, ctrb_darwin2_ckpt62x_20110513, ctrb_darwin2_ckpt62w_20110426, ctrb_darwin2_ckpt63o_20120629, ctrb_darwin2_ckpt64e_20130305, ctrb_darwin2_ckpt63c_20111011, ctrb_darwin2_ckpt63i_20120124, ctrb_darwin2_ckpt63m_20120506, ctrb_darwin2_ckpt63s_20120908, ctrb_darwin2_ckpt63e_20111107, ctrb_darwin2_ckpt63b_20110830, ctrb_darwin2_ckpt63j_20120217, ctrb_darwin2_ckpt63r_20120817, ctrb_darwin2_ckpt64g_20130503, ctrb_darwin2_ckpt64l_20130806, ctrb_darwin2_ckpt63g_20111220, ctrb_darwin2_ckpt64c_20130120, ctrb_darwin2_ckpt63a_20110804, ctrb_darwin2_ckpt64j_20130704, ctrb_darwin2_ckpt63h_20111230, ctrb_darwin2_ckpt63p_20120707, ctrb_darwin2_ckpt63d_20111107, ctrb_darwin2_ckpt63q_20120731, ctrb_darwin2_ckpt63_20110728, ctrb_darwin2_ckpt64b_20121224, ctrb_darwin2_ckpt64d_20130219, ctrb_darwin2_ckpt64_20121012, ctrb_darwin2_baseline, ctrb_darwin2_ckpt63n_20120604, ctrb_darwin2_ckpt63k_20120317, ctrb_darwin2_ckpt62z_20110622
darwin2 initial checkin

1 jahn 1.1 #include "CPP_OPTIONS.h"
2     #include "PTRACERS_OPTIONS.h"
3     #include "DARWIN_OPTIONS.h"
4    
5     #ifdef ALLOW_PTRACERS
6     #ifdef ALLOW_DARWIN
7    
8     #ifdef ALLOW_CARBON
9    
10    
11     SUBROUTINE DIC_READ_PICKUP(
12     O pH_isLoaded,
13     I myIter, myThid )
14    
15     IMPLICIT NONE
16     C === Global variables ===
17     #include "SIZE.h"
18     #include "EEPARAMS.h"
19     #include "PARAMS.h"
20     #include "DARWIN_FLUX.h"
21    
22     C == Routine arguments ==
23     C myThid :: my Thread Id number
24     LOGICAL pH_isLoaded
25     INTEGER myIter
26     INTEGER myThid
27    
28    
29     C !FUNCTIONS
30    
31     C !LOCAL VARIABLES:
32     C == Local variables ==
33     CHARACTER*(MAX_LEN_FNAM) fn, filNam
34     CHARACTER*(MAX_LEN_MBUF) msgBuf
35     LOGICAL useCurrentDir, fileExist
36     INTEGER fp, ioUnit
37     CEOP
38    
39     pH_isLoaded =.FALSE.
40     ioUnit = errorMessageUnit
41    
42     C-- pickup file name :
43     IF (pickupSuff.EQ.' ') THEN
44     WRITE(fn,'(A,I10.10)') 'pickup_dic.', myIter
45     ELSE
46     WRITE(fn,'(A,A10)') 'pickup_dic.', pickupSuff
47     ENDIF
48     fp = precFloat64
49    
50     C-- First check if pickup file exist
51     #ifdef ALLOW_MDSIO
52     useCurrentDir = .FALSE.
53     CALL MDS_CHECK4FILE(
54     I fn, '.data', 'DIC_READ_PICKUP',
55     O filNam, fileExist,
56     I useCurrentDir, myThid )
57     #else
58     STOP 'ABNORMAL END: S/R DIC_READ_PICKUP: Needs MDSIO pkg'
59     #endif
60    
61     IF ( fileExist ) THEN
62     C-- Read pickup file
63     CALL READ_REC_3D_RL( fn, fp, 1, pH, 1, myIter, myThid )
64     pH_isLoaded = .TRUE.
65    
66     _EXCH_XY_RL( pH, myThid )
67     ELSE
68     pH_isLoaded = .FALSE.
69     IF ( pickupStrictlyMatch ) THEN
70     WRITE(msgBuf,'(4A)') 'DIC_READ_PICKUP: ',
71     & 'try with " pickupStrictlyMatch=.FALSE.,"',
72     & ' in file: "data", NameList: "PARM03"'
73     CALL PRINT_MESSAGE( msgBuf, ioUnit, SQUEEZE_RIGHT, myThid )
74     STOP 'ABNORMAL END: S/R DIC_READ_PICKUP'
75     ELSE
76     WRITE(msgBuf,'(2A)') 'WARNING >> DIC_READ_PICKUP: ',
77     & 'will restart from approximated pH'
78     CALL PRINT_MESSAGE( msgBuf, ioUnit, SQUEEZE_RIGHT, myThid )
79     ENDIF
80     ENDIF
81    
82    
83     RETURN
84     END
85     #endif /*ALLOW_CARBON*/
86    
87     #endif /*DARWIN*/
88     #endif /*ALLOW_PTRACERS*/
89     c ==================================================================

  ViewVC Help
Powered by ViewVC 1.1.22