source: CPL/oasis3/trunk/src/mod/oasis3/src/dealloc_src.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: 17.6 KB
Line 
1!                       ****************************
2!                       * DEALLOCATION SUBROUTINES *
3!                       ****************************
4SUBROUTINE dealloc_anais
5!
6!**** DEALLOC_ANAIS
7!
8!     Purpose:
9!       Deallocate arrays defined in the "anais" module
10!
11!     Interface:
12!       none
13!   
14!     Method:
15!       Deallocation of arrays allocated in "alloc_anais" or "inipar_alloc"
16!
17!     External:
18!       none
19!
20!     Files:
21!       none
22!   
23!     References:
24!
25!     History:
26!     --------
27!       Version   Programmer     Date        Description
28!       ------------------------------------------------
29!       2.5       A.Caubel       2002/03/18  created
30!
31!*-----------------------------------------------------------------------
32!
33!** + DECLARATIONS
34!
35!** ++ Use of modules
36!
37  USE mod_kinds_oasis
38  USE mod_anais
39!
40!** ++ Local declarations
41!
42  INTEGER (kind=ip_intwp_p) :: il_err
43!
44!*-----------------------------------------------------------------------
45!
46  DEALLOCATE (varmul, stat=il_err)
47  DEALLOCATE (niwtm)
48  DEALLOCATE (niwtg)
49  DEALLOCATE (linit)
50  DEALLOCATE (ngint)
51  DEALLOCATE (nmint)
52  DEALLOCATE (nmesh)
53  DEALLOCATE (agint)
54  DEALLOCATE (amint)
55  IF (allocated(naismfl)) DEALLOCATE (naismfl)
56  IF (allocated(naismvoi)) DEALLOCATE (naismvoi)
57  IF (allocated(naisgfl)) DEALLOCATE (naisgfl)
58  IF (allocated(naisgvoi)) DEALLOCATE (naisgvoi)
59 
60!
61!*-----------------------------------------------------------------------
62!
63END SUBROUTINE dealloc_anais
64!
65!*========================================================================
66SUBROUTINE dealloc_analysis
67!
68!**** DEALLOC_ANALYSIS
69!
70!     Purpose:
71!       Deallocate arrays defined in the "analysis" module
72!
73!     Interface:
74!       none
75!   
76!     Method:
77!       Deallocation of arrays allocated in "alloc_analysis".     
78!
79!     External:
80!       none
81!
82!     Files:
83!       none
84!   
85!     References:
86!
87!     History:
88!     --------
89!       Version   Programmer     Date        Description
90!       ------------------------------------------------
91!       2.5       A.Caubel       2002/03/18  created
92!
93!*-----------------------------------------------------------------------
94!
95!** + DECLARATIONS
96!
97!** ++ Use of modules
98!
99  USE mod_analysis
100!
101!*-----------------------------------------------------------------------
102!
103  IF (allocated(ntronca)) DEALLOCATE (ntronca)
104  DEALLOCATE (ncofld)
105  DEALLOCATE (neighborg)
106  DEALLOCATE (nludat)
107  DEALLOCATE (nlufil)
108  DEALLOCATE (nlumap)
109  DEALLOCATE (nlusub)
110  DEALLOCATE (nluext)
111  DEALLOCATE (nosper)
112  DEALLOCATE (notper)
113  DEALLOCATE (ntinpflx)
114  DEALLOCATE (ntoutflx)
115  DEALLOCATE (amskval)
116  DEALLOCATE (amskvalnew)
117  DEALLOCATE (acocoef)
118  DEALLOCATE (abocoef)
119  DEALLOCATE (abncoef)
120  DEALLOCATE (afldcoef)
121  DEALLOCATE (afldcobo)
122  DEALLOCATE (afldcobn)
123  DEALLOCATE (cxordbf)
124  DEALLOCATE (cyordbf)
125  DEALLOCATE (cxordaf)
126  DEALLOCATE (cyordaf)
127  DEALLOCATE (cgrdtyp)
128  DEALLOCATE (cfldtyp)
129  DEALLOCATE (cfilfic)
130  DEALLOCATE (cfilmet)
131  DEALLOCATE (cconmet)
132  DEALLOCATE (cfldcoa)
133  DEALLOCATE (cfldfin)
134  DEALLOCATE (ccofld)
135  DEALLOCATE (cbofld)
136  DEALLOCATE (cbnfld)
137  DEALLOCATE (ccofic)
138  DEALLOCATE (cdqdt)
139  DEALLOCATE (cgrdmap)
140  DEALLOCATE (cmskrd)
141  DEALLOCATE (cgrdsub)
142  DEALLOCATE (ctypsub)
143  DEALLOCATE (cgrdext)
144  DEALLOCATE (csper)
145  DEALLOCATE (ctper)
146  DEALLOCATE (lsurf)
147  DEALLOCATE (nscripvoi)
148  DEALLOCATE (cmap_method)
149  DEALLOCATE (cfldtype)
150  DEALLOCATE (crsttype)
151  DEALLOCATE (nbins)
152  DEALLOCATE (cnorm_opt)
153  DEALLOCATE (corder)
154!* Vector case
155  IF (lg_vector) THEN
156      DEALLOCATE (cg_assoc_input_field)
157      DEALLOCATE (ig_assoc_input_field)
158      DEALLOCATE (lrotate)
159  ENDIF
160!
161  IF (allocated(cintmet)) DEALLOCATE(cintmet)
162  IF (allocated(cextmet)) DEALLOCATE(cextmet)
163  IF (allocated(neighbor)) DEALLOCATE(neighbor)
164  IF (allocated(nextfl)) DEALLOCATE(nextfl)
165  IF (allocated(nbofld)) DEALLOCATE(nbofld)
166  IF (allocated(nbnfld)) DEALLOCATE(nbnfld)
167  IF (allocated(nmapvoi)) DEALLOCATE(nmapvoi)
168  IF (allocated(nmapfl)) DEALLOCATE(nmapfl)
169  IF (allocated(nsubfl)) DEALLOCATE(nsubfl)
170  IF (allocated(nsubvoi)) DEALLOCATE(nsubvoi)
171 
172!
173!*-----------------------------------------------------------------------
174!
175END SUBROUTINE dealloc_analysis
176!
177!*========================================================================
178SUBROUTINE dealloc_coast
179!
180!**** DEALLOC_COAST
181!
182!     Purpose:
183!       Deallocate arrays defined in the "coast" module
184!
185!     Interface:
186!       none
187!   
188!     Method:
189!       Deallocation of arrays allocated in "alloc_coast".     
190!
191!     External:
192!       none
193!
194!     Files:
195!       none
196!   
197!     References:
198!
199!     History:
200!     --------
201!       Version   Programmer     Date        Description
202!       ------------------------------------------------
203!       2.5       A.Caubel       2002/03/18  created
204!
205!*-----------------------------------------------------------------------
206!
207!** + DECLARATIONS
208!
209!** ++ Use of modules
210!
211
212
213  USE mod_coast
214!
215!*-----------------------------------------------------------------------
216!
217  DEALLOCATE (npcoast)
218!
219!*-----------------------------------------------------------------------
220!
221END SUBROUTINE dealloc_coast
222!
223!*========================================================================
224SUBROUTINE dealloc_experiment
225!
226!**** DEALLOC_EXPERIMENT
227!
228!     Purpose:
229!       Deallocate arrays defined in the "experiment" module
230!
231!     Interface:
232!       none
233!   
234!     Method:
235!       Deallocation of arrays allocated in "alloc_experiment".       
236!
237!     External:
238!       none
239!
240!     Files:
241!       none
242!   
243!     References:
244!
245!     History:
246!     --------
247!       Version   Programmer     Date        Description
248!       ------------------------------------------------
249!       2.5       A.Caubel       2002/03/18  created
250!
251!*-----------------------------------------------------------------------
252!
253!** + DECLARATIONS
254!
255!** ++ Use of modules
256!
257  USE mod_experiment
258!
259!*-----------------------------------------------------------------------
260!
261  DEALLOCATE (nbcplproc)
262  DEALLOCATE (nbtotproc)
263  DEALLOCATE (cmodnam)
264  DEALLOCATE (cmpiarg)
265  DEALLOCATE (iga_unitmod)
266!
267!*-----------------------------------------------------------------------
268!
269END SUBROUTINE dealloc_experiment
270!
271!*========================================================================
272SUBROUTINE dealloc_extrapol
273!
274!**** DEALLOC_EXTRAPOL
275!
276!     Purpose:
277!       Deallocate arrays defined in the "extrapol" module
278!
279!     Interface:
280!       none
281!   
282!     Method:
283!       Deallocation of arrays allocated in "alloc_extrapol".       
284!
285!     External:
286!       none
287!
288!     Files:
289!       none
290!   
291!     References:
292!
293!     History:
294!     --------
295!       Version   Programmer     Date        Description
296!       ------------------------------------------------
297!       2.5       A.Caubel       2002/03/18  created
298!
299!*-----------------------------------------------------------------------
300!
301!** + DECLARATIONS
302!
303!** ++ Use of modules
304!
305  USE mod_extrapol
306!
307!*-----------------------------------------------------------------------
308!
309  DEALLOCATE (niwtn)
310  DEALLOCATE (niwtng)
311  IF (allocated(nninnfl)) DEALLOCATE(nninnfl)
312  IF (allocated(nninnflg)) DEALLOCATE (nninnflg)
313  DEALLOCATE (lextra)
314  DEALLOCATE (lweight)
315  DEALLOCATE (aextra)
316  DEALLOCATE (nextra)
317  DEALLOCATE (lextrapdone)
318  IF (allocated(iaddress)) DEALLOCATE (iaddress)
319  IF (allocated(iincre)) DEALLOCATE (iincre)
320  IF (allocated(zweights)) DEALLOCATE (zweights)
321!
322!*-----------------------------------------------------------------------
323!
324END SUBROUTINE dealloc_extrapol
325!
326!*========================================================================
327SUBROUTINE dealloc_memory
328!
329!**** DEALLOC_MEMORY
330!
331!     Purpose:
332!       Deallocate arrays defined in the "memory" module
333!
334!     Interface:
335!       none
336!   
337!     Method:
338!       Deallocation of arrays allocated in "alloc_memory".       
339!
340!     External:
341!       none
342!
343!     Files:
344!       none
345!   
346!     References:
347!
348!     History:
349!     --------
350!       Version   Programmer     Date        Description
351!       ------------------------------------------------
352!       2.5       A.Caubel       2002/03/18  created
353!
354!*-----------------------------------------------------------------------
355!
356!** + DECLARATIONS
357!
358!** ++ Use of modules
359!
360  USE mod_memory
361!
362!*-----------------------------------------------------------------------
363!
364  DEALLOCATE (nsizold)
365  DEALLOCATE (nsiznew)
366  DEALLOCATE (nadrold)
367  DEALLOCATE (nadrold_grid)
368  DEALLOCATE (nadrnew)
369  DEALLOCATE (nadrnew_grid)
370  DEALLOCATE (mskold)
371  DEALLOCATE (msknew)
372  DEALLOCATE (fldold)
373  DEALLOCATE (xgrold)
374  DEALLOCATE (ygrold)
375  DEALLOCATE (surold)
376  DEALLOCATE (fldnew)
377  DEALLOCATE (xgrnew)
378  DEALLOCATE (ygrnew)
379  DEALLOCATE (surnew)
380  DEALLOCATE (nwork)
381  DEALLOCATE (work)
382!
383!*-----------------------------------------------------------------------
384!
385END SUBROUTINE dealloc_memory
386!
387!*========================================================================
388SUBROUTINE dealloc_nproc
389!
390!**** DEALLOC_NPROC
391!
392!     Purpose:
393!       Deallocate arrays defined in the "nproc" module
394!
395!     Interface:
396!       none
397!   
398!     Method:
399!       Deallocation of arrays allocated in "alloc_nproc".       
400!
401!     External:
402!       none
403!
404!     Files:
405!       none
406!   
407!     References:
408!
409!     History:
410!     --------
411!       Version   Programmer     Date        Description
412!       ------------------------------------------------
413!       2.5       A.Caubel       2002/03/18  created
414!
415!*-----------------------------------------------------------------------
416!
417!** + DECLARATIONS
418!
419!** ++ Use of modules
420!
421  USE mod_nproc
422!
423!*-----------------------------------------------------------------------
424!
425  DEALLOCATE (nproc)
426!
427!*-----------------------------------------------------------------------
428!
429END SUBROUTINE dealloc_nproc
430!
431!*========================================================================
432SUBROUTINE dealloc_parallel
433!
434!**** DEALLOC_ANALYSIS
435!
436!     Purpose:
437!       Deallocate arrays defined in the "parallel" module
438!
439!     Interface:
440!       none
441!   
442!     Method:
443!       Deallocation of arrays allocated in "alloc_parallel".       
444!
445!     External:
446!       none
447!
448!     Files:
449!       none
450!   
451!     References:
452!
453!     History:
454!     --------
455!       Version   Programmer     Date        Description
456!       ------------------------------------------------
457!       2.5       A.Caubel       2002/03/18  created
458!
459!*-----------------------------------------------------------------------
460!
461!** + DECLARATIONS
462!
463!** ++ Use of modules
464!
465  USE mod_parallel
466!
467!*-----------------------------------------------------------------------
468!
469  DEALLOCATE (nparal)
470  DEALLOCATE (cparal)
471!
472!*-----------------------------------------------------------------------
473!
474END SUBROUTINE dealloc_parallel
475!
476!*========================================================================
477SUBROUTINE dealloc_pipe
478!
479!**** DEALLOC_PIPE
480!
481!     Purpose:
482!       Deallocate arrays defined in the "pipe" module
483!
484!     Interface:
485!       none
486!   
487!     Method:
488!       Deallocation of arrays allocated in "alloc_pipe".       
489!
490!     External:
491!       none
492!
493!     Files:
494!       none
495!   
496!     References:
497!
498!     History:
499!     --------
500!       Version   Programmer     Date        Description
501!       ------------------------------------------------
502!       2.5       A.Caubel       2002/03/18  created
503!
504!*-----------------------------------------------------------------------
505!
506!** + DECLARATIONS
507!
508!** ++ Use of modules
509!
510  USE mod_pipe
511!
512!*-----------------------------------------------------------------------
513!
514  DEALLOCATE (cprnam)
515  DEALLOCATE (cpwnam)
516!
517!*-----------------------------------------------------------------------
518!
519END SUBROUTINE dealloc_pipe
520!
521!*========================================================================
522SUBROUTINE dealloc_rainbow
523!
524!**** DEALLOC_RAINBOW
525!
526!     Purpose:
527!       Deallocate arrays defined in the "rainbow" module
528!
529!     Interface:
530!       none
531!   
532!     Method:
533!       Deallocation of arrays allocated in "alloc_rainbow".       
534!
535!     External:
536!       none
537!
538!     Files:
539!       none
540!   
541!     References:
542!
543!     History:
544!     --------
545!       Version   Programmer     Date        Description
546!       ------------------------------------------------
547!       2.5       A.Caubel       2002/03/18  created
548!
549!*-----------------------------------------------------------------------
550!
551!** + DECLARATIONS
552!
553!** ++ Use of modules
554!
555  USE mod_rainbow
556!
557!*-----------------------------------------------------------------------
558!
559  DEALLOCATE (lmapp)
560  DEALLOCATE (lsubg)
561  DEALLOCATE (amapp)
562  DEALLOCATE (asubg)
563  DEALLOCATE (nmapp)
564  DEALLOCATE (nsubg)
565!
566!*-----------------------------------------------------------------------
567!
568END SUBROUTINE dealloc_rainbow
569!
570!*========================================================================
571SUBROUTINE dealloc_sipc
572!
573!**** DEALLOC_SIPC
574!
575!     Purpose:
576!       Deallocate arrays defined in the "sipc" module
577!
578!     Interface:
579!       none
580!   
581!     Method:
582!       Deallocation of arrays allocated in "alloc_sipc".       
583!
584!     External:
585!       none
586!
587!     Files:
588!       none
589!   
590!     References:
591!
592!     History:
593!     --------
594!       Version   Programmer     Date        Description
595!       ------------------------------------------------
596!       2.5       A.Caubel       2002/03/18  created
597!
598!*-----------------------------------------------------------------------
599!
600!** + DECLARATIONS
601!
602!** ++ Use of modules
603!
604  USE mod_sipc
605!
606!*-----------------------------------------------------------------------
607!
608  DEALLOCATE (mpoolidin)
609  DEALLOCATE (mpoolidou)
610  DEALLOCATE (mpoolinitr)
611  DEALLOCATE (mpoolinitw)
612!
613!*-----------------------------------------------------------------------
614!
615END SUBROUTINE dealloc_sipc
616!
617!*========================================================================
618SUBROUTINE dealloc_string
619!
620!**** DEALLOC_SIPC
621!
622!     Purpose:
623!       Deallocate arrays defined in the "string" module
624!
625!     Interface:
626!       none
627!   
628!     Method:
629!       Deallocation of arrays allocated in "alloc_string".       
630!
631!     External:
632!       none
633!
634!     Files:
635!       none
636!   
637!     References:
638!
639!     History:
640!     --------
641!       Version   Programmer     Date        Description
642!       ------------------------------------------------
643!       2.5       A.Caubel       2002/03/18  created
644!
645!*-----------------------------------------------------------------------
646!
647!** + DECLARATIONS
648!
649!** ++ Use of modules
650!
651  USE mod_string
652  USE mod_parameter
653!
654!*-----------------------------------------------------------------------
655!
656  IF (lg_oasis_field) THEN
657     DEALLOCATE (numlab)
658     DEALLOCATE (nfexch)
659     DEALLOCATE (nluinp)
660     DEALLOCATE (nluout)
661     DEALLOCATE (nseqn)
662     DEALLOCATE (nlagn)
663     DEALLOCATE (cnaminp)
664     DEALLOCATE (cnamout)
665     DEALLOCATE (cficinp)
666     DEALLOCATE (cficout)
667     DEALLOCATE (cstate)
668     DEALLOCATE (ig_portin_id)
669     DEALLOCATE (ig_portout_id)
670     DEALLOCATE (cficbf)
671     DEALLOCATE (cficaf)
672     DEALLOCATE (nlonbf)
673     DEALLOCATE (nlatbf)
674     DEALLOCATE (nlonaf)
675     DEALLOCATE (nlataf)
676     DEALLOCATE (ig_ntrans)
677     DEALLOCATE (canal)
678     DEALLOCATE (ig_grid_nbrbf)
679     DEALLOCATE (ig_grid_nbraf)
680  ENDIF
681
682  DEALLOCATE (ig_lag)
683  DEALLOCATE (lg_state)
684  DEALLOCATE (ig_no_rstfile)
685  DEALLOCATE (cg_name_rstfile)
686  DEALLOCATE (ig_numlab)
687  DEALLOCATE (ig_freq)
688  DEALLOCATE (ig_total_nseqn)
689  DEALLOCATE (cg_input_field)
690  DEALLOCATE (cg_output_field)
691  DEALLOCATE (ig_total_state)
692  DEALLOCATE (ig_local_trans)
693  DEALLOCATE (cg_input_file)
694  DEALLOCATE (ig_number_field)
695  DEALLOCATE (ig_total_ntrans)
696  DEALLOCATE (cg_restart_file)
697  DEALLOCATE (cga_locatorbf)
698  DEALLOCATE (cga_locatoraf)
699  DEALLOCATE (ig_invert)
700  DEALLOCATE (ig_reverse)
701!
702!*-----------------------------------------------------------------------
703!
704END SUBROUTINE dealloc_string
705!
706!*========================================================================
707SUBROUTINE dealloc_timestep
708!
709!**** DEALLOC_SIPC
710!
711!     Purpose:
712!       Deallocate arrays defined in the "timestep" module
713!
714!     Interface:
715!       none
716!   
717!     Method:
718!       Deallocation of arrays allocated in "alloc_timestep".       
719!
720!     External:
721!       none
722!
723!     Files:
724!       none
725!   
726!     References:
727!
728!     History:
729!     --------
730!       Version   Programmer     Date        Description
731!       ------------------------------------------------
732!       2.5       A.Caubel       2002/03/18  created
733!
734!*-----------------------------------------------------------------------
735!
736!** + DECLARATIONS
737!
738!** ++ Use of modules
739!
740  USE mod_timestep
741!
742!*-----------------------------------------------------------------------
743!
744  DEALLOCATE (mstep)
745  DEALLOCATE (mfcpl)
746  DEALLOCATE (mdt)
747!
748!*-----------------------------------------------------------------------
749!
750END SUBROUTINE dealloc_timestep
751!
752!*========================================================================
753SUBROUTINE dealloc_unitncdf
754!
755!**** DEALLOC_UNITNCDF
756!
757!     Purpose:
758!       Deallocate arrays defined in the "unitncdf" module
759!
760!     Interface:
761!       none
762!   
763!     Method:
764!       Deallocation of arrays allocated in "alloc_unitncdf".       
765!
766!     External:
767!       none
768!
769!     Files:
770!       none
771!   
772!     References:
773!
774!     History:
775!     --------
776!       Version   Programmer     Date        Description
777!       ------------------------------------------------
778!       2.5       A.Caubel       2002/03/18  created
779!
780!*-----------------------------------------------------------------------
781!
782!** + DECLARATIONS
783!
784!** ++ Use of modules
785!
786  USE mod_unitncdf
787!
788!*-----------------------------------------------------------------------
789!
790  DEALLOCATE (nc_inpid)
791  DEALLOCATE (nc_outid)
792!
793!*-----------------------------------------------------------------------
794!
795END SUBROUTINE dealloc_unitncdf
796!
797!*========================================================================
Note: See TracBrowser for help on using the repository browser.