modules.f90 16.53 KiB
      module module_precision
      ! wp=working precision
      integer, parameter :: wp = kind(1.0d0)
      end module
      !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
      module module_laplacien
      use module_precision
      implicit none
      real(WP),dimension(:,:),allocatable::xbb,ybb,xybb
      real(WP),dimension(:),allocatable::a11,a22,a12,deta
      end module
      !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
      module module_tableaux
      use module_precision
      implicit none
      !tableaux dynamiques
      integer,dimension(:,:),allocatable::iae
      integer,dimension(:),allocatable::nne
      integer,dimension(:,:),allocatable::ine
      integer,dimension(:,:),allocatable::ieve
      integer,dimension(:,:),allocatable::ina
      integer,dimension(:,:),allocatable::ieva
      integer,dimension(:),allocatable::nrefa
      integer,dimension(:),allocatable::nae,neva,nevn
      integer,dimension(:,:),allocatable::ievn
      real(WP),dimension(:,:),allocatable::dxe
      real(WP),dimension(:),allocatable::dxen
      real(WP),dimension(:),allocatable::xna,yna,xta,yta
      real(WP),dimension(:),allocatable::xn,yn
      real(WP),dimension(:),allocatable::xe,ye
      real(WP),dimension(:),allocatable::xa,ya
      real(WP),dimension(:),allocatable::zfa
      real(WP),dimension(:),allocatable::zfe
      real(WP),dimension(:),allocatable::zfn
      real(WP),dimension(:),allocatable::fra,fre
      real(WP),dimension(:),allocatable::hal,qnal,qtal
      real(WP),dimension(:),allocatable::het,quet,qvet
      real(WP),dimension(:),allocatable::he,que,qve
      real(WP),dimension(:),allocatable::pxzfe,pyzfe,pxque,pyque,pxqve,pyqve
      real(WP),dimension(:),allocatable::pxhe,pyhe
      real(WP),dimension(:),allocatable::pxze,pyze
      real(WP),dimension(:),allocatable::se,la
      real(WP),dimension(:),allocatable::px2que,py2que,px2qve,py2qve
      real(WP),dimension(:),allocatable::hae
      real(WP),dimension(:),allocatable::smbu,smbv
      real(WP),dimension(:),allocatable::smbu2,smbv2
      real(WP),dimension(:),allocatable::smbu3,smbv3
      real(WP),dimension(:),allocatable::fha,fqua,fqva
      real(WP),dimension(:,:),allocatable::houv,qouv,difqouvp
      real(WP),dimension(:,:),allocatable::xae,yae
      real(WP),dimension(:),allocatable::pxqu,pxqv,pyqu,pyqv
      real(WP),dimension(:,:),allocatable::hg1,qug1,qvg1
      real(WP),dimension(:),allocatable::fluu,flvv
      real(WP),dimension(:),allocatable::cvia
7172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140
real(WP),dimension(:),allocatable::ncvi real(WP),dimension(:),allocatable::cofr real(WP),dimension(:,:),allocatable::flgu,flgv real(WP),dimension(:,:),allocatable::vouv,vtouv integer,dimension(:),allocatable::napp real(WP),dimension(:),allocatable::smbh integer,dimension(:),allocatable::nven real(WP),dimension(:),allocatable::kse logical,dimension(:),allocatable::eau real(WP) :: alpha ! nombre maxi d'elements, aretes, noeuds etc ... integer, parameter :: naemax = 4, nnemax = 4 integer, parameter :: nevemx = 4, nnamax = 2 integer, parameter :: nevamx = 2, nalmax = 1000 integer, parameter :: nlimmax=300, noumax=25000, noemax=5 ! nltmax : nombre maximal de courbes de tarage ! nplmax : nombre maximal de points sur une courbe de tarage ! ntrmax : taille maximale du tableau des resultats de rupture progressive integer, parameter :: nltmax=100, nplmax=500, ntrmax=9000 ! nobmax : nombre maximal d'ouvrages de type b integer, parameter :: nobmax=100 !autres commons integer :: ne, na, nn integer :: nas, iac(nalmax) integer :: icfl, iosmb, iclvar, iapp, iofr real(WP) :: prec integer :: nitmax integer :: ifen, irep integer :: ifdm, ifm, ifin, ifli, ifro, ifcl, ifci, ifr, ifrt integer :: ifap, ifve integer :: nbpt, ienb(nlimmax) !integer :: k character(len=255) :: etude real(WP) :: eps1, eps2, paray integer :: ift real(WP) :: g real(WP) :: fro, fvix, fviy real(WP) :: zfm real(WP) :: tm,tr,tinit,tmax real(WP) :: dt,cfl,dt0,t real(WP) :: qlt(nltmax,nplmax),zlt(nltmax,nplmax) integer :: ialt(nltmax),nblt(nltmax),iltmax integer :: ie1(noumax),ie2(noumax),ia1(noumax),ia2(noumax) integer :: j1(noumax),j2(noumax),nouv(noumax),nbouv real(WP) :: long(noumax,noemax),zdev(noumax,noemax) real(WP) :: haut(noumax,noemax),coef(noumax,noemax) character(len=1) :: typouv(noumax,noemax) integer :: nbcou1(noumax,noemax),nbcou2(noumax,noemax) real(WP) :: qcoup(noumax*noemax*noemax) real(WP) :: zcoup(noumax*noemax*noemax) real(WP) :: volouv(noumax) logical :: lcvi,lcviv,lcvif character(len=8) :: schema real(WP) :: dtr,dtrc real(WP) :: volo(noumax),voli,vole,vols logical :: tnou logical :: debut logical :: debglo,debtar integer :: na60 real(WP) :: trc ! variables relatives aux ouvrages c logical :: ext1(noumax,noemax),ext2(noumax,noemax) integer :: ieamont(noumax,noemax),ieaval(noumax,noemax) logical :: controlet(noumax,noemax) real(wp) :: qcoup2(noumax*noemax*noemax),zcoup2(noumax*noemax*noemax) integer :: nbcou12(noumax),nbcou22(noumax) character*1 :: typouv2(noumax)
141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210
real(wp) :: long2(noumax),zdev2(noumax),haut2(noumax),coef2(noumax),tcoup2(noumax) integer :: nvaltz1(noumax,noemax),nvaltz2(noumax,noemax) ! variables relatives a la rupture progressive (ouvrage b) real(WP) :: zc(nobmax),zp(nobmax),alp(nobmax) real(WP) :: alc(nobmax),z0(nobmax),d50(nobmax),rho(nobmax) real(WP) :: phi(nobmax),db0(nobmax),zb0(nobmax) real(WP) :: eta(nobmax),ka(nobmax),c1(nobmax) real(WP) :: c2(nobmax),dt2(nobmax) integer :: nt(nobmax) real(WP) :: ym(nobmax),sm(nobmax),pm(nobmax) real(WP) :: rhm(nobmax),alm(nobmax),nu(nobmax) real(WP) :: ql(ntrmax,nobmax),qs(ntrmax,nobmax) real(WP) :: dbr(ntrmax,nobmax),z(ntrmax,nobmax) real(WP) :: zav(ntrmax,nobmax),zbr(ntrmax,nobmax) real(WP) :: zb(nobmax),db(nobmax) integer :: it(nobmax) real(WP) :: largmail(nobmax),trect(nobmax) logical :: kappa(nobmax) integer :: ioub(noumax,noemax),nob integer :: ouv(nobmax) logical :: elap(nobmax),suivan(nobmax) !010618 MB coefficient erosion lineaire, MBLINEAIRE logical logical mblineaire(nobmax) double precision mb(nobmax) real(WP) :: tini(nobmax) real(WP) :: dbprec(nobmax) ! variables relatives aux apports de pluie ! nombre maximal de chroniques et de nombre de couples par chronique integer, parameter :: nmchro=10000,nmcoap=1000 real(WP) :: appchr(nmchro,nmcoap),tappch(nmchro,nmcoap) !vents real(WP) :: ventx(nmchro,nmcoap),venty(nmchro,nmcoap) real(WP) :: tvent(nmchro,nmcoap) logical :: pven real(WP) :: fvix0,fviy0 ! formule de frottement logical :: darcy real(WP) :: latitude logical :: coriolis integer :: nchro,nbchro(nmchro) integer :: nchrov,nbchrv(nmchro) !real(wp)::tcomm1,tcomm2,tcomm ! file identifiers integer, parameter :: id_ze = 47 integer, parameter :: id_dzf = 48 integer, parameter :: id_tps = 44 integer, parameter :: id_tpc = 57 integer, parameter :: id_zfn = 46 integer, parameter :: id_nua = 34 integer, parameter :: id_mas = 59 integer, parameter :: id_hyc = 58 integer, parameter :: id_tar = 45 integer, parameter :: id_app = 30 integer, parameter :: id_eve_ven = 31 integer, parameter :: id_res = 110 integer :: idl = 0 end module !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! module module_tevent use module_precision implicit none
211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280
real(WP),dimension(:),allocatable::xvent,yvent end module !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! module module_loc use module_precision implicit none ! subroutine lenv real(WP),save,dimension(:),allocatable:: hem,qum,qvm real(WP),dimension(:),allocatable::hem2,qum2,qvm2 real(WP),dimension(:),allocatable::th,tu !subroutine grdlp real(WP),dimension(:,:),allocatable::xaa,yaa logical,dimension(:),allocatable::hezer real(WP),dimension(:),allocatable::a110,a220,a120,deta0 real(WP),dimension(:),allocatable::sse !subroutine laplaf real(WP),dimension(:),allocatable::fxuu,fyuu,fxvv,fyvv,pxuu,pyuu,pxvv,pyvv,ue,ve,ustar !subroutine flvla2 real(WP),dimension(:),allocatable::dh,dqu,dqv !subroutine qouvr real(WP),dimension(:,:),allocatable::qouvp !subroutine secmb1 real(WP),dimension(:),allocatable::hed end module !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! module module_mpi use module_precision implicit none integer::me,nab,np,statinfo,scribe integer::naloc,nbouv_b_loc,nmv integer::nnloc,nnb !integer,dimension(mpi_status_size)::status integer::nbouvloc,nouvb integer::group_world,group_calcul,comm_calcul !integer::mpi_comm_world integer,dimension(:),allocatable :: aretes_loc,aretes_bord integer,dimension(:),allocatable :: noeuds_loc,noeuds_bord integer,dimension(:),allocatable :: nb_elt_send_proc,nb_elt_recv_proc integer,dimension(:),allocatable :: aretes_loc_all,mailles_loc_all,noeuds_loc_all integer,dimension(:),allocatable :: ouvragesb_loc,mailles_loc integer,dimension(:),allocatable :: ouvrages_loc,ouvrages_bord integer,dimension(:),allocatable :: elt_voisins,vecteur_message integer,dimension(:),allocatable :: nb_mailles_recues,deplacements integer,dimension(:),allocatable :: nb_aretes_recues,deplacements2 integer,dimension(:),allocatable :: nb_noeuds_recus,deplacements3 integer,dimension(:),allocatable :: elt_bord,vecteur_reception integer,dimension(:),allocatable::procouvb,machine integer,dimension(:),allocatable::ne_loc real(wp),dimension(:),allocatable::message,message2 real(wp),dimension(:),allocatable::message_scribe,message_scribe2,message_scribe4 real(wp),dimension(:),allocatable::reception_scribe,reception_scribe2,reception_scribe4 integer,dimension(:),allocatable::reception_scribe4int,message_scribe4int logical,dimension(:),allocatable::message_scribe3,reception_scribe3 integer,dimension(:),allocatable::deplacement_send_proc,deplacement_recv_proc logical,dimension(:),allocatable::message_logical,message_logical2 integer::nploc
281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350
integer,dimension(31:59)::machine_aretes30 integer,dimension(61:89)::machine_aretes60 integer,dimension(:),allocatable::machine_ias integer,dimension(:),allocatable::deplacement_message_c,deplacement_reception_c integer,dimension(:),allocatable::nb_elt_message_c,nb_elt_reception_c integer,dimension(:),allocatable::vecteur_message_c,vecteur_reception_c real(wp),dimension(:),allocatable::message_c,reception_c end module !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! module module_lecl use module_precision implicit none integer, parameter :: nalmax = 1000 integer,parameter::ltmax=1000 integer nt,k2,na30 real(WP) tcl(ltmax),hat(nalmax,ltmax),qnat(nalmax,ltmax),qtat(nalmax,ltmax),hcat(nalmax,ltmax)& &,diamt(nalmax,ltmax),sigmat(nalmax,ltmax) end module module cgns_data use module_precision implicit none integer :: nb_timesteps_cgns,index_file,index_base,index_zone, index_section character(32) :: sol_names_temp integer :: dim(2) type c32vector character(len=32),allocatable,dimension(:) :: values integer vectsize integer realsize integer base end type c32vector type(c32vector) :: sol_names,sol_names2 type(c32vector) :: gridmotionpointers,gridcoordpointers type ivector integer,allocatable,dimension(:) :: values integer vectsize integer realsize end type ivector type dvector real*8,allocatable,dimension(:) :: values integer vectsize integer realsize end type dvector type(dvector) :: times_cgns contains subroutine c32_push_back(x, newvalue) class(c32vector),intent(inout) :: x character(len=32),intent(in) :: newvalue integer :: newsize character(len=32),allocatable :: tmp(:) ! ici on ajoute newvalue
351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420
! si x est trop petit, on double sa taille jusqu'à ce que ça soit assez grand do while (x%realsize < x%vectsize + 1) newsize = x%realsize*2 allocate(tmp(newsize)) ! on double la taille allouée tmp(1:x%vectsize) = x%values(1:x%vectsize) !on copie les anciennes valeurs de x call move_alloc(tmp, x%values) ! x pointe sur l'espace mémoire de tmp, tmp est désalloué x%realsize = newsize ! x a maintenant la place d'accueilir newvalue end do ! on a plus qu'à ajouter newvalue x%values(x%vectsize+1) = newvalue ! on n'oublie pas d'augmenter la taille de x x%vectsize = x%vectsize + 1 end subroutine c32_push_back subroutine d_push_back(x, newvalue) class(dvector),intent(inout) :: x real*8,intent(in) :: newvalue integer :: newsize real*8,dimension(:),allocatable :: tmp ! ici on ajoute newvalue ! si x est trop petit, on double sa taille jusqu'à ce que ça soit assez grand do while (x%realsize < x%vectsize + 1) newsize = x%realsize*2 allocate(tmp(newsize)) ! on double la taille allouée tmp(1:x%vectsize) = x%values(1:x%vectsize) !on copie les anciennes valeurs de x call move_alloc(tmp, x%values) ! x pointe sur l'espace mémoire de tmp, tmp est désalloué x%realsize = newsize ! x a maintenant la place d'accueilir newvalue end do ! on a plus qu'à ajouter newvalue x%values(x%vectsize+1) = newvalue ! on n'oublie pas d'augmenter la taille de x x%vectsize = x%vectsize + 1 end subroutine d_push_back subroutine i_push_back(x, newvalue) class(ivector),intent(inout) :: x integer,intent(in) :: newvalue integer :: newsize integer,dimension(:),allocatable :: tmp ! ici on ajoute newvalue ! si x est trop petit, on double sa taille jusqu'à ce que ça soit assez grand do while (x%realsize < x%vectsize + 1) newsize = x%realsize*2 allocate(tmp(newsize)) ! on double la taille allouée tmp(1:x%vectsize) = x%values(1:x%vectsize) !on copie les anciennes valeurs de x call move_alloc(tmp, x%values) ! x pointe sur l'espace mémoire de tmp, tmp est désalloué x%realsize = newsize ! x a maintenant la place d'accueilir newvalue end do ! on a plus qu'à ajouter newvalue x%values(x%vectsize+1) = newvalue ! on n'oublie pas d'augmenter la taille de x x%vectsize = x%vectsize + 1 end subroutine i_push_back subroutine c32_allocate(x, vect_size) type(c32vector),intent(inout) :: x integer,intent(in) :: vect_size allocate (x%values(vect_size)) x%realsize = vect_size x%vectsize = 0 end subroutine c32_allocate subroutine i_allocate(x, vect_size) type(ivector),intent(inout) :: x integer,intent(in) :: vect_size
421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457
allocate (x%values(vect_size)) x%realsize = vect_size x%vectsize = 0 end subroutine i_allocate subroutine d_allocate(x, vect_size) type(dvector),intent(inout) :: x integer,intent(in) :: vect_size allocate (x%values(vect_size)) x%realsize = vect_size x%vectsize = 0 end subroutine d_allocate subroutine c32_deallocate(x) type(c32vector),intent(inout) :: x deallocate (x%values) x%realsize = 0 x%vectsize = 0 end subroutine c32_deallocate subroutine i_deallocate(x) type(ivector),intent(inout) :: x deallocate (x%values) x%realsize = 0 x%vectsize = 0 end subroutine i_deallocate subroutine d_deallocate(x) type(dvector),intent(inout) :: x deallocate (x%values) x%realsize = 0 x%vectsize = 0 end subroutine d_deallocate end module cgns_data