/[MITgcm]/MITgcm/pkg/exf/exf_interp_read.F
ViewVC logotype

Contents of /MITgcm/pkg/exf/exf_interp_read.F

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


Revision 1.2 - (show annotations) (download)
Tue Nov 8 15:53:41 2005 UTC (18 years, 7 months ago) by cnh
Branch: MAIN
Changes since 1.1: +2 -2 lines
Changes toward getting exf working multi-threaded.
  o added some opitonal consistency check in barrier for
    trapping barrier calls in singel threaded region
  o removed a single thread block in ini_depths - singleCpuIO
    still broken.
  o modified parts of exf_ that were setting local stack variables
    in single threaded section and then referencing them from all
    threads.
  o commented out strange stop in mdsio for multithreading which
    seems uneeded.
  o fixed ptracers initialization and changed ptracers monitor
    to avoid race condition in which several threads set a shared
    logical flag at arbitrary moments with respect to each other

1 #include "EXF_OPTIONS.h"
2 CCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCC
3 C Flux Coupler using C
4 C Bilinear interpolation of forcing fields C
5 C C
6 C B. Cheng (12/2002) C
7 C C
8 C added Bicubic (bnc 1/2003) C
9 C C
10 CCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCC
11
12 SUBROUTINE exf_interp_read(
13 I infile,
14 I filePrec,
15 O arrayin,
16 I irecord, xG, yG,
17 I lon_0, lon_inc,
18 I lat_0, lat_inc,
19 I nx_in, ny_in, method, mythid)
20
21 implicit none
22
23 C infile = name of the input file (direct access binary)
24 C filePrec = file precicision (currently not used, assumes real*4)
25 C arrout = output arrays (different for each processor)
26 C irecord = record number in global file
27 C xG,yG = coordinates for output grid
28 C lon_0, lat_0 = lon and lat of sw corner of global input grid
29 C lon_inc = scalar x-grid increment
30 C lat_inc = vector y-grid increments
31 C nx_in, ny_in = input x-grid and y-grid size
32 C method = 1 for bilinear 2 for bicubic
33 C mythid = thread id
34 C
35
36 #include "SIZE.h"
37 #include "EEPARAMS.h"
38 #ifdef ALLOW_USE_MPI
39 # include "EESUPPORT.h"
40 #endif /* ALLOW_USE_MPI */
41 #include "PARAMS.h"
42
43 C subroutine variables
44 character*(*) infile
45 integer filePrec, irecord, nx_in, ny_in
46 real*4 arrayin(-1:nx_in+2 , -1:ny_in+2)
47 _RS xG (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
48 _RS yG (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
49 _RL lon_0, lon_inc
50 _RL lat_0, lat_inc(ny_in-1)
51 integer method, mythid
52
53 C Functions
54 integer MDS_RECLEN
55
56 C local variables
57 integer ierr, length_of_rec
58 real*8 ne_fac,nw_fac,se_fac,sw_fac
59 integer e_ind(snx,sny),w_ind(snx,sny)
60 integer n_ind(snx,sny),s_ind(snx,sny)
61 real*8 px_ind(4), py_ind(4), ew_val(4)
62 external lagran
63 real*8 lagran
64 integer i, j, k, l, js, bi, bj, sp, interp_unit
65 real*4 global(nx_in,ny_in)
66
67 C _BEGIN_MASTER( myThid )
68
69 C check input arguments
70 if ( .NOT. (filePrec .EQ. 32) )
71 & stop 'stop in exf_interp.F: value of filePrec not allowed'
72
73 C read in input data
74 #ifdef ALLOW_USE_MPI
75 if (useSingleCPUIO) then
76
77 C master thread of process 0, only, opens a global file
78 IF( mpiMyId .EQ. 0 ) THEN
79 call mdsfindunit( interp_unit, mythid)
80 length_of_rec=MDS_RECLEN( filePrec, nx_in*ny_in, mythid )
81 open(interp_unit,file=infile,status='old',access='direct',
82 & recl=length_of_rec)
83 read(interp_unit,rec=irecord)
84 & ((global(i,j),i=1,nx_in),j=1,ny_in)
85 close(interp_unit)
86 ENDIF
87
88 C broadcast to all processes
89 call MPI_BCAST(global,nx_in*ny_in,MPI_REAL,
90 & 0,MPI_COMM_MODEL,ierr)
91 do j=1,ny_in
92 do i=1,nx_in
93 arrayin(i,j)=global(i,j)
94 enddo
95 enddo
96
97 else
98 #endif /* ALLOW_USE_MPI */
99
100 call mdsfindunit( interp_unit, mythid)
101 length_of_rec=MDS_RECLEN( filePrec, nx_in*ny_in, mythid )
102 open(interp_unit,file=infile,status='old',access='direct',
103 & recl=length_of_rec)
104 read(interp_unit,rec=irecord)
105 & ((arrayin(i,j),i=1,nx_in),j=1,ny_in)
106 close(interp_unit)
107
108 #ifdef ALLOW_USE_MPI
109 endif
110 #endif /* ALLOW_USE_MPI */
111
112 #ifdef _BYTESWAPIO
113 call MDS_BYTESWAPR4((nx_in+4)*(ny_in+4), arrayin )
114 #endif /* _BYTESWAPIO */
115
116 C _END_MASTER( myThid )
117
118 END

  ViewVC Help
Powered by ViewVC 1.1.22