source: branches/iLoveclim/SOURCES/util_recovery.f90 @ 146

Last change on this file since 146 was 146, checked in by aquiquet, 7 years ago

Grisli-iLoveclim branch: merged to trunk at revision 145

File size: 4.4 KB
Line 
1!> \file util_recovery.f90
2!! Module avec les routines d'initialisation et de test des sortie cptr ou nc
3!<
4
5!> \namespace util_recovery
6!! This module gathers routines to read and write cptr files
7!! \author BAYA Hassine
8!! \date Septembre 2010
9!! @note Used module
10!! @note   - use module3D_phy
11!<
12
13
14module util_recovery
15  use module3D_phy
16  implicit none
17  double precision    ,dimension(:),allocatable :: tab_time
18  double precision                              :: dtout
19  real*8, dimension(:), pointer                 :: time_out
20  logical                                       :: logic_out 
21contains
22
23  !> SUBROUTINE: init_recovery
24  !! Initialise les sorties recovery pas de temps et temps de sortie
25  !>
26
27  subroutine init_recovery
28    implicit none
29
30    integer            :: num_file = 22 
31    integer            :: i,j
32    character (len=10) :: comment   
33
34    if (itracebug.eq.1)  call tracebug(' Entree dans routine init_recovery ')
35
36    !open(num_file,file='../SOURCES/Fichiers-parametres/TEMPS-CPTR-NC.dat')
37    !open(num_file,file=trim(dirsource)//'/Fichiers-parametres/TEMPS-CPTR-NC.dat')
38    open(num_file,file=trim(dirsource)//'/TEMPS-CPTR-NC.dat')
39
40    ! passe les commentaires qui se terminent par une ligne de ~~~
41    comment1: do
42       read(num_file,'(a10)') comment
43       if (comment.eq.'~~~~~~~~~~') exit comment1
44    end do comment1
45
46    ! lecture de dtcpt
47    read(num_file,*) dtout
48    read(num_file,*)       !saut de la ligne "-------"
49    read(num_file,*) i
50    if (.not. allocated(tab_time)) then ! aurel dec15
51       allocate(tab_time(i))
52    end if
53    do j=1,i 
54       read(num_file,*)   tab_time(j)
55    end do
56
57    comment2: do   
58       read(num_file,'(a10)') comment
59       if (comment .eq. '----------')  exit comment2               
60    end do comment2
61
62    !fin de lecture
63    close(num_file)
64    return
65  end subroutine init_recovery
66
67  !> SUBROUTINE: testout_recovery
68  !! Test si on effectue les sorties des fichiers de reprise
69  !>
70
71  subroutine testout_recovery(filin)
72    implicit none
73    real                           :: difftime 
74    integer                        :: indice
75    integer                        :: ipredef
76    character(len=*),intent(inout) :: filin
77    character(len=10)              :: ntime
78    character(len=1)               :: signe,unite
79
80    if (itracebug.eq.1)  call tracebug(' Entree dans routine testout_recovery ')
81    if (.not.associated(time_out)) then
82       allocate(time_out(1)) 
83    end if
84
85    ipredef=0
86    logic_out=.FALSE.
87
88    ! aurel, dec15. en plus des id avec des "k" etc. on va rajouter
89    ! un identifiant "grestart" pour identifier ces .nc restarts
90    ! des autres
91 
92    predef: do indice=1,size(tab_time)
93      difftime=abs(TIME-tab_time(indice))
94      if ( difftime.lt.dtmin ) then
95        ipredef=1
96        time_out(1)=tab_time(indice)
97        exit predef
98      end if
99    end do predef
100
101    if ((mod(abs(dble(TIME)),dble(DTOUT)).lt.dble(dtmin)).OR.   &
102         (ABS(TIME+297000).LT.dtmin) .OR.   &
103         (ABS(TIME+126000).LT.dtmin) .OR.   &
104         (ABS(TIME+21000) .LT.dtmin) .OR.   &
105         (ABS(TIME+16000) .LT.dtmin) .OR.   & 
106         (TIME .EQ. TEND).OR.(ipredef.eq.1) )    THEN
107
108       if (ipredef .EQ. 1) then
109         ! pour changer de signe entre le passe et le futur
110         if (tab_time(indice).GT.0.) then
111          signe= '+'
112         else
113          signe= '-'
114         endif
115
116        if (int(mod(abs(tab_time(indice)),1000.)).eq.0) then
117!     temps multiple de 1000
118          unite='k'
119          write(ntime,'(i10)') int(abs(tab_time(indice)/1000.))
120        else if (int(mod(abs(tab_time(indice)),100.)).eq.0) then
121!     temps multiple de 100
122          unite='c'
123          write(ntime,'(i10)') int(abs(tab_time(indice)/100.))
124        else if (int(mod(abs(tab_time(indice)),10.)).eq.0) then
125!     temps multiple de 10
126          unite='d'
127          write(ntime,'(i10)') int(abs(tab_time(indice)/10.))
128        else
129!     temps en annees
130          unite='a'
131          write(ntime,'(i10)') int(abs(tab_time(indice)/1.))
132        endif
133        filin=runname//'-grestart'//signe//unite//trim(ADJUSTL(ntime))
134
135     else !ipredef==0
136        if (TIME .ge. Tend) then
137           time_out(1)=TIME
138           filin=runname//'-grestart_2'
139        else
140           time_out(1)=TIME
141           filin=runname//'-grestart_1'
142        end if
143     end if
144     logic_out=.TRUE.
145  endif
146
147  end subroutine testout_recovery
148
149
150end module util_recovery
Note: See TracBrowser for help on using the repository browser.