source: CPL/oasis3/trunk/src/mod/oasis3/src/alloc.f90 @ 1677

Last change on this file since 1677 was 1677, checked in by aclsce, 12 years ago

Imported oasis3 (tag ipslcm5a) from cvs server to svn server (igcmg project).

File size: 2.2 KB
Line 
1SUBROUTINE alloc (id_flag)
2!
3!
4!**** INIALLOC
5!
6!     Purpose:
7!       Allocate arrays defined in the modules
8!
9!     Interface:
10!       none
11!   
12!     Method:
13!       Uses run parameters read in "inipar_alloc" routine to
14!       allocate arrays.       
15!
16!     External:
17!       none
18!
19!     Files:
20!       none
21!   
22!     References:
23!
24!     History:
25!     --------
26!       Version   Programmer     Date        Description
27!       ------------------------------------------------
28!       2.5       A.Caubel       2002/03/18  created
29!
30!*-----------------------------------------------------------------------
31!
32!** + DECLARATIONS
33!
34!** ++ Use of modules
35!
36  USE mod_parameter
37!
38!* ---------------------------- Local declarations ----------------------
39!
40     INTEGER (kind=ip_intwp_p) :: id_flag
41!
42!*-----------------------------------------------------------------------
43!
44IF (id_flag .EQ. 1) THEN
45!** + Module mod_experiment
46!
47  CALL alloc_experiment
48!
49!** + Module mod_string
50!
51  CALL alloc_string
52!
53!** + Following routines will be called only if one field (at least) goes
54!     through Oasis 
55!
56  IF (lg_oasis_field) THEN 
57!
58!** + Module mod_anais
59!
60     CALL alloc_anais1
61!
62!** + Module mod_analysis
63!
64     CALL alloc_analysis
65!
66!** + Module mod_coast
67!
68     CALL alloc_coast
69!
70!** + Module mod_extrapol
71!
72     CALL alloc_extrapol1 
73!
74!** + Module mod_memory
75!
76     CALL alloc_memory1
77!
78!** + Module mod_nproc
79!
80     CALL alloc_nproc
81!
82!** + Module mod_parallel
83!
84     CALL alloc_parallel
85!
86!** + Module mod_pipe
87!
88     CALL alloc_pipe
89!
90!** + Module mod_rainbow
91!
92     CALL alloc_rainbow1
93!
94!** + Module mod_sipc
95!
96     CALL alloc_sipc
97!
98!** + Module mod_timestep
99!
100     CALL alloc_timestep
101!
102!** + Module mod_unitncdf
103!
104     CALL alloc_unitncdf
105!
106  ENDIF
107ELSE
108  IF (lg_oasis_field) THEN 
109!
110!** + Module mod_anais
111!
112     CALL alloc_anais2
113!
114!** + Module mod_extrapol
115!
116     CALL alloc_extrapol2 
117!
118!** + Module mod_memory
119!
120     CALL alloc_memory2
121!
122!** + Module mod_rainbow
123!
124     CALL alloc_rainbow2
125!
126   ENDIF
127ENDIF
128!*------------------------------------------------------------------------
129!
130END SUBROUTINE alloc
131!
132!*========================================================================
133
Note: See TracBrowser for help on using the repository browser.