source: trunk/SOURCES/util_recovery.f90 @ 4

Last change on this file since 4 was 4, checked in by dumas, 10 years ago

initial import GRISLI trunk

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