source: CPL/oasis3/trunk/src/lib/psmile/src/prism_put_restart_proto.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.6 KB
Line 
1  SUBROUTINE prism_put_restart_proto (id_port_id, kstep, kinfo)
2!
3!*    *** PRISM_put ***   PRISM 1.0
4!
5!     purpose:
6!     --------
7!        write buffered field corresponding to port id_port_id in its
8!        restart coupling file
9!
10!     interface:
11!     ----------
12!        id_port_id : port number of the field
13!        kstep  : current time in seconds
14!        kinfo  : output status
15!
16!     lib mp:
17!     -------
18!        mpi-1
19!
20!     author:
21!     -------
22!         Sophie Valcke (07/03 - created from prism_put_proto)
23!     ----------------------------------------------------------------
24    USE mod_kinds_model
25    USE mod_prism_proto
26    USE mod_comprism_proto
27    IMPLICIT NONE
28#include <mpif.h>
29!     ----------------------------------------------------------------
30    INTEGER (kind=ip_intwp_p)      kstep, kinfo, id_port_id
31!     ----------------------------------------------------------------
32    INTEGER (kind=ip_intwp_p)      iport
33!     ----------------------------------------------------------------
34!
35!*    0. First check
36!     --------------
37!
38    IF (nexit.ne.1) THEN
39       kinfo = CLIM_FastExit
40       WRITE(nulprt,FMT='(A)') 'Put_restart - should not be called'
41       GO TO 1010
42    ENDIF
43    kinfo = PRISM_Ok
44!
45!*    1. check for this port in my list
46!     ---------------------------------
47!
48    iport = -1
49!
50!   Test if the field is defined in the namcouple and if its coupling period
51!   is not greater than the time of the simulation.
52    IF (ig_def_freq(id_port_id) .eq. 0.or. &
53         ig_def_freq(id_port_id) .gt. ig_ntime) THEN
54       GOTO 1010
55    ENDIF
56!
57    IF (myport(1,id_port_id).eq.CLIM_Out) THEN
58       iport=id_port_id
59    ENDIF
60    IF (iport.lt.0) THEN
61       kinfo = CLIM_BadPort
62       WRITE(nulprt,FMT='(A,A)') &
63            'Put - WARNING - Invalid port out: ', &
64            cports(id_port_id)
65       GO TO 1010
66    ENDIF
67!
68!*  Field is written to restart file
69    IF (lg_dgfield) THEN
70        IF (mydist(CLIM_Strategy,iport) .EQ. CLIM_Serial) THEN
71            CALL write_filer8(dg_field_trans(:,iport),cports(iport),iport)
72        ELSE
73            CALL write_file_parar8(dg_field_trans(:,iport),cports(iport),iport)
74        ENDIF
75    ELSE
76        IF (mydist(CLIM_Strategy,iport) .EQ. CLIM_Serial) THEN
77            CALL write_filer8(rg_field_trans(:,iport),cports(iport),iport)
78        ELSE
79            CALL write_file_parar8(rg_field_trans(:,iport),cports(iport),iport)
80        ENDIF
81    ENDIF
82    kinfo = PRISM_ToRest
83!
84!     ----------------------------------------------------------------
85!
861010 CONTINUE
87    CALL FLUSH(nulprt)
88!
89  END SUBROUTINE prism_put_restart_proto
90
Note: See TracBrowser for help on using the repository browser.