source: trunk/SOURCES/util_recovery.f90 @ 334

Last change on this file since 334 was 142, checked in by dumas, 7 years ago

Debug output suppressed and bug correction in calving

File size: 4.1 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
39    ! passe les commentaires qui se terminent par une ligne de ~~~
40    comment1: do
41       read(num_file,'(a10)') comment
42       if (comment.eq.'~~~~~~~~~~') exit comment1
43    end do comment1
44
45    ! lecture de dtcpt
46    read(num_file,*) dtout
47    read(num_file,*)       !saut de la ligne "-------"
48    read(num_file,*) i
49    if (.not. allocated(tab_time)) then ! aurel dec15
50       allocate(tab_time(i))
51    end if
52    do j=1,i 
53       read(num_file,*)   tab_time(j)
54    end do
55   
56    comment2: do   
57       read(num_file,'(a10)') comment
58       if (comment .eq. '----------')  exit comment2               
59    end do comment2
60
61    !fin de lecture
62    close(num_file)
63    return
64  end subroutine init_recovery
65
66  !> SUBROUTINE: testout_recovery
67  !! Test si on effectue les sorties des fichiers de reprise
68  !>
69
70  subroutine testout_recovery(filin)
71    implicit none
72    real                           :: difftime 
73    integer                        :: indice
74    integer                        :: ipredef
75    character(len=*),intent(inout) :: filin
76    character(len=10)              :: ntime
77    character(len=1)               :: signe,unite
78
79    if (itracebug.eq.1)  call tracebug(' Entree dans routine testout_recovery ')
80    if (.not.associated(time_out)) then
81       allocate(time_out(1)) 
82    end if
83
84    ipredef=0
85    logic_out=.FALSE.
86 
87    predef: do indice=1,size(tab_time)
88      difftime=abs(TIME-tab_time(indice))
89      if ( difftime.lt.dtmin ) then
90        ipredef=1
91        time_out(1)=tab_time(indice)
92        exit predef
93      end if
94    end do predef
95
96    if ((mod(abs(dble(TIME)),dble(DTOUT)).lt.dble(dtmin)).OR.   &
97         (ABS(TIME+297000).LT.dtmin) .OR.   &
98         (ABS(TIME+126000).LT.dtmin) .OR.   &
99         (ABS(TIME+21000) .LT.dtmin) .OR.   &
100         (ABS(TIME+16000) .LT.dtmin) .OR.   & 
101         (TIME .EQ. TEND).OR.(ipredef.eq.1) )    THEN
102
103       if (ipredef .EQ. 1) then
104         ! pour changer de signe entre le passe et le futur
105         if (tab_time(indice).GT.0.) then
106          signe= '+'
107         else
108          signe= '-'
109         endif
110
111        if (int(mod(abs(tab_time(indice)),1000.)).eq.0) then
112!     temps multiple de 1000
113          unite='k'
114          write(ntime,'(i10)') int(abs(tab_time(indice)/1000.))
115        else if (int(mod(abs(tab_time(indice)),100.)).eq.0) then
116!     temps multiple de 100
117          unite='c'
118          write(ntime,'(i10)') int(abs(tab_time(indice)/100.))
119        else if (int(mod(abs(tab_time(indice)),10.)).eq.0) then
120!     temps multiple de 10
121          unite='d'
122          write(ntime,'(i10)') int(abs(tab_time(indice)/10.))
123        else
124!     temps en annees
125          unite='a'
126          write(ntime,'(i10)') int(abs(tab_time(indice)/1.))
127        endif
128        filin=runname//signe//unite//trim(ADJUSTL(ntime))
129
130      else !ipredef==0
131        if (TIME .ge. Tend) then
132          time_out(1)=TIME
133          filin=runname//'_2'
134        else
135          time_out(1)=TIME
136          filin=runname//'_1'
137        end if
138      end if
139      logic_out=.TRUE.
140    endif
141
142  end subroutine testout_recovery
143
144
145end module util_recovery
Note: See TracBrowser for help on using the repository browser.