source: trunk/SOURCES/util_recovery.f90 @ 55

Last change on this file since 55 was 29, checked in by dumas, 9 years ago

Mise a jour pour etre compatible avec le code couple iLOVECLIM

File size: 3.5 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
78    if (itracebug.eq.1)  call tracebug(' Entree dans routine testout_recovery ')
79    if (.not.associated(time_out)) then
80       allocate(time_out(1)) 
81    end if
82
83    ipredef=0
84    logic_out=.FALSE.
85
86    if ((mod(abs(dble(TIME)),dble(DTOUT)).lt.dble(dtmin)).OR.   &
87         (ABS(TIME+297000).LT.dtmin) .OR.   &
88         (ABS(TIME+126000).LT.dtmin) .OR.   &
89         (ABS(TIME+21000) .LT.dtmin) .OR.   &
90         (ABS(TIME+16000) .LT.dtmin) .OR.   & 
91         (TIME .EQ. TEND)                  )    THEN
92
93       predef: do indice=1,size(tab_time)
94          difftime=abs(TIME-tab_time(indice))
95          if ( difftime.lt.dtmin ) then
96             ipredef=1
97             time_out(1)=tab_time(indice)
98             exit predef
99          end if
100       end do predef
101
102       if (ipredef .EQ. 1) then
103          write(ntime,'(i10)')  INT(abs(dble(tab_time(indice)))/dble(DTOUT)) 
104          if (tab_time(indice) .Lt. 0) then
105             filin=runname//'-k'//trim(ADJUSTL(ntime))
106          else
107             filin=runname//'+k'//trim(ADJUSTL(ntime))
108          end if
109
110       else !ipredef==0
111          if (TIME .ge. Tend) then
112             time_out(1)=TIME
113             filin=runname//'_2'
114          else
115             time_out(1)=TIME
116             filin=runname//'_1'
117          end if
118       end if
119       logic_out=.TRUE.
120    endif
121
122  end subroutine testout_recovery
123
124
125end module util_recovery
Note: See TracBrowser for help on using the repository browser.