1 |
sannino |
1.1 |
C $Header: /u/gcmpack/MITgcm/pkg/oasis/oasis_init.F,v 1.0 2005/07/18 23:05:09 gianamria sannino Exp $ |
2 |
|
|
C $Name: $ |
3 |
|
|
|
4 |
|
|
cgm( |
5 |
|
|
#include "CPP_EEOPTIONS.h" |
6 |
|
|
cgm) |
7 |
|
|
#include "OASIS_OPTIONS.h" |
8 |
|
|
C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----| |
9 |
|
|
CBOP 0 |
10 |
|
|
C !ROUTINE: OASIS_INIT |
11 |
|
|
|
12 |
|
|
C !INTERFACE: |
13 |
|
|
c SUBROUTINE OASIS_INIT( myThid,ciccio ) |
14 |
|
|
SUBROUTINE OASIS_INIT (MPI_COMM_OASIS) |
15 |
|
|
|
16 |
|
|
|
17 |
|
|
|
18 |
|
|
C !DESCRIPTION: |
19 |
|
|
C Routine to initialize OASIS parameters and variables. |
20 |
|
|
|
21 |
|
|
C !USES: |
22 |
|
|
USE mod_kinds_model |
23 |
|
|
USE mod_prism_proto |
24 |
|
|
c USE mod_prism_def_partition_proto |
25 |
|
|
c USE mod_prism_put_proto |
26 |
|
|
c USE mod_prism_get_proto |
27 |
|
|
c USE mod_prism_grids_writing |
28 |
|
|
IMPLICIT NONE |
29 |
|
|
cgm) |
30 |
|
|
#include "SIZE.h" |
31 |
|
|
#include "EEPARAMS.h" |
32 |
|
|
#include "EESUPPORT.h" |
33 |
|
|
#include "PARAMS.h" |
34 |
|
|
#include "GRID.h" |
35 |
|
|
cgm( qui vanno inseriuti anche se il pkg non รจ ancora attivato...piccola porcata |
36 |
|
|
#include "OASIS.h" |
37 |
|
|
#include "OASIS_PARAMS.h" |
38 |
|
|
cgm) |
39 |
|
|
C !INPUT PARAMETERS: |
40 |
|
|
INTEGER myThid |
41 |
|
|
CEOP |
42 |
|
|
|
43 |
|
|
C !LOCAL VARIABLES: |
44 |
|
|
#ifdef ALLOW_OASIS |
45 |
|
|
INTEGER :: io_size, ii, il_real, il_bufsizebyt |
46 |
|
|
INTEGER :: integer_byte_size, integer_io_size,il_bufsize |
47 |
|
|
INTEGER :: MPI_COMM_OASIS |
48 |
|
|
REAL(kind=ip_realwp_p), DIMENSION(Nx,Ny) :: rla_array |
49 |
|
|
REAL(kind=ip_realwp_p), DIMENSION(:), ALLOCATABLE :: rla_bufsend |
50 |
|
|
c-------- define model name ------- |
51 |
|
|
cp_modnam='mitgcm' ! Component model name |
52 |
|
|
c--------------------------- |
53 |
|
|
|
54 |
|
|
|
55 |
|
|
! |
56 |
|
|
! 1- PSMILe initialization |
57 |
|
|
! |
58 |
|
|
CALL prism_init_comp_proto (il_comp_id, cp_modnam, ierror) |
59 |
|
|
! |
60 |
|
|
! Let's suppose the model attaches to a MPI buffer for its own use |
61 |
|
|
! |
62 |
|
|
! ! Sophisticated way to determine buffer size needed (without "kind") |
63 |
|
|
! ! Here one message containing rla_array |
64 |
|
|
|
65 |
|
|
integer_byte_size = BIT_SIZE(ii)/8 |
66 |
|
|
INQUIRE (iolength=io_size) ii |
67 |
|
|
integer_io_size = io_size |
68 |
|
|
INQUIRE (iolength=io_size) rla_array(1,1) |
69 |
|
|
il_real = io_size/integer_io_size*integer_byte_size |
70 |
|
|
il_bufsize = (Nx*Ny) + MPI_BSEND_OVERHEAD/il_real + 1 |
71 |
|
|
ALLOCATE (rla_bufsend(il_bufsize), stat = ierror) |
72 |
|
|
il_bufsizebyt = il_bufsize * il_real |
73 |
|
|
CALL MPI_Buffer_Attach(rla_bufsend, il_bufsizebyt, ierror) |
74 |
|
|
|
75 |
|
|
IF (ierror .NE. PRISM_Ok) THEN |
76 |
|
|
WRITE (*,*) ' mit : pb prism_init_comp_proto' |
77 |
|
|
CALL prism_abort_proto(il_comp_id, 'mit.F90','abort1') |
78 |
|
|
ELSE |
79 |
|
|
WRITE(*,*) 'mit : prism_init_comp_proto ok ' |
80 |
|
|
ENDIF |
81 |
|
|
|
82 |
|
|
! |
83 |
|
|
! 2- PSMILe attribution of local communicator. |
84 |
|
|
! |
85 |
|
|
! Either MPI_COMM_WORLD if MPI2 is used, |
86 |
|
|
! Either a local communicator created by Oasis if MPI1 is used. |
87 |
|
|
! |
88 |
|
|
CALL prism_get_localcomm_proto(il_commlocal, ierror) |
89 |
|
|
! |
90 |
|
|
IF (ierror .NE. PRISM_Ok) THEN |
91 |
|
|
WRITE (*,*) ' mit : pb prism_init_comp_proto' |
92 |
|
|
CALL prism_abort_proto(il_comp_id, 'atm.F90','abort2') |
93 |
|
|
ELSE |
94 |
|
|
WRITE(*,*) 'mit : prism_init_comp_proto ok ' |
95 |
|
|
ENDIF |
96 |
|
|
|
97 |
|
|
MPI_COMM_OASIS = il_commlocal ! Set local communicator for mitgcm |
98 |
|
|
|
99 |
|
|
999 CONTINUE |
100 |
|
|
|
101 |
|
|
|
102 |
|
|
|
103 |
|
|
#endif /* ALLOW_OASIS */ |
104 |
|
|
|
105 |
|
|
return |
106 |
|
|
end |