Changeset 467


Ignore:
Timestamp:
01/26/24 16:49:00 (4 months ago)
Author:
aquiquet
Message:

Cleaning branch: continuing module3D cleaning

Location:
branches/GRISLIv3/SOURCES
Files:
20 edited

Legend:

Unmodified
Added
Removed
  • branches/GRISLIv3/SOURCES/3D-physique-gen_mod.f90

    r465 r467  
    6363  real ::  V_limit                      !< vitesse maxi (limitateur de flux pour conserv masse) 
    6464  real ::  betamax                      !< (Pa) frottement maxi sous les streams 
    65   real ::  pvimin                       !< valeur de pvi pour les noeuds fictifs 
    6665 
    6766 
     
    7776 
    7877  integer,dimension(nx,ny) :: FRONT     !< point d'un shelf situe sur le front 
    79   integer,dimension(nx,ny) :: FRONTFACEX!< type de front sur les faces x 
    80   integer,dimension(nx,ny) :: FRONTFACEY!< type de front sur les faces y 
    8178  integer,dimension(nx,ny) :: gr_line_schoof ! points ou on impose le flux de schoof (pour sorties) 
    8279  integer,dimension(nx,ny) :: gr_line   !< points grounding line pour les sorties 
     
    8885  integer,dimension(nx,ny) :: Mk_init      !< initial mask (with islands, outcrops, ... 
    8986  integer,dimension(nx,ny) :: MK           !< masks (ice sheet, max, above water, below water, 1) 
    90   integer,dimension(nx,ny) :: MNEG         !< masks (ice sheet, max, above water, below water, 1) 
    9187  integer,dimension(nx,ny) :: IBASE     !< type de base (froide, temperee) 
    9288 
     
    9591  real,dimension(nx,ny) :: ABLBORD      !< Ablation dans les zones non englacees 
    9692  real,dimension(nx,ny) :: ablbord_dtt  !< Ablation sur le bord de la calotte (flux de glace inférieur à ablation sur le bord) sur dtt 
    97   real,dimension(nx,ny) :: ACQUA        !< Surface des surfaces en eau 
    9893  double precision,dimension(nx,ny) :: B            !< Altitude de la base de la glace  'o' 
    9994  real,dimension(nx,ny) :: BDOT         !< derivee de B / t 
    100   real,dimension(nx,ny) :: B1           !<  
    10195  double precision,dimension(nx,ny) :: BSOC0        !< ice free bedrock 
    102   real,dimension(nx,ny) :: betamx       !< coefficient beta du frottement basal 
    103   ! betamx=cf*neffmx et tobmx=betamx*uxbar 
    104   real,dimension(nx,ny) :: betamy       !< coefficient beta du frottement basal 
    105   ! betamy=cf*neffmy et tobmy=betamy*uybar 
    106   !hassine 
     96  real,dimension(nx,ny) :: betamx       !< coefficient beta du frottement basal, betamx=cf*neffmx et tobmx=betamx*uxbar 
     97  real,dimension(nx,ny) :: betamy       !< coefficient beta du frottement basal, betamy=cf*neffmy et tobmy=betamy*uybar 
    10798  real, dimension(nx,ny) :: beta_centre !< beta on major node (average) 
    10899  real, dimension(nx,ny) :: betamax_2d  !< (Pa) frottement maxi sous les streams 
     
    116107  real,dimension(nx,ny) :: CALV         !< calving 
    117108   
    118   !real,dimension(:,:,:),allocatable :: DDX  ! pour le calcul de UX  
    119   !real,dimension(:,:,:),allocatable :: DDY  ! pour le calcul de UY 
    120109  real,dimension(nx,ny) :: DDBX         !< UBX/(-SDX) '>' 
    121110  real,dimension(nx,ny) :: DDBY         !< UBY/(-SDY) '^' 
     
    123112  real,dimension(nx,ny) :: Diffmy       !< partie diffusive en y 
    124113 
    125   !REAL,dimension(nx,ny) :: DPHIX        !< ROG*HMX**2  '>' 
    126   !REAL,dimension(nx,ny) :: DPHIY        !< ROG*HMY**2  '^' 
    127114  real,dimension(nx,ny) :: DHDT         !< derive lagrangienne de l'epaisseur 'o' 
    128   real,dimension(nx,ny) :: DIF1         !< UZR(I,J,1)-BM(I,J) 
    129   real,dimension(nx,ny) :: DIF2         !< UZR(I,J,1)-BMELT(I,J) 
    130   real,dimension(nx,ny) :: DIFT         !< pour sorties eismint 
    131   real,dimension(nx,ny) :: DIVU         !< divergence de UH 
    132   ! real,dimension(nx,ny) :: DISTCENT     !  
    133   real,dimension(nx,ny) :: ELA          !< Equilibrium line altitude, for mass balance 
    134115  real,dimension(nx,ny) :: epsxx     !< vitesse de deformation selon x 
    135116  real,dimension(nx,ny) :: epsyy     !< vitesse de deformation selon y 
     
    141122  real,dimension(nx,ny) :: FROTMY       !<  
    142123  real,dimension(nx,ny) :: GHF          !< geothermal heat flux J/m2/a 'o' 
    143   real,dimension(nx,ny) :: GHF0         !< geothermal heat flux J/m2/a 'o' 
    144124  double precision,dimension(nx,ny) :: H            !< ice thickness  'o' 
    145125  double precision,dimension(nx,ny) :: H0           !< initial ice thickness, must be initialized before init_iso 
     
    148128  real,dimension(nx,ny)    :: Hp           !< H value if prescribed 
    149129  real,dimension(nx,ny)    :: Hp0          !< H value if prescribed (reference value) 
    150 !  real,dimension(nx,ny)    :: Delta_H      !< Delta_H value if prescribed 
    151 !  integer,dimension(nx,ny) :: i_delta_H    !< 1 if Delta_H is prescribed on this node, else 0 
    152130  integer,dimension(nx,ny) :: i_Hp         !< 1 if H is prescribed on this node, else 0 
    153131  integer,dimension(nx,ny) :: i_Hp0        !< i_hp mask reference value does not change with time 
    154132  integer, dimension(nx,ny) :: imx_diag    !< masque pour eq elliptique   
    155133  integer, dimension(nx,ny) :: imy_diag    !< masque pour eq elliptique  
    156   integer,dimension(nx,ny) :: MK_gl0       !< mask grounding line initial 
    157   integer,dimension(nx,ny) :: MK_flot0     !< mask float initial 
    158  
    159134 
    160135  double precision,dimension(nx,ny) :: HDOT         !< ice thickness derivee / t 
    161136  real,dimension(nx,ny) :: HDOTWATER 
    162   real,dimension(nx,ny) :: H1           !<  
    163137  real,dimension(nx,ny) :: HMX          !< ice thickness moy selon x '>' 
    164138  real,dimension(nx,ny) :: HMY          !< ice thickness moy selon y '^' 
    165   real,dimension(nx,ny) :: HDOTPREC     !<  
    166   real,dimension(nx,ny) :: HDOTRAP      !<  
    167  
    168   real,dimension(nx,ny) :: KOND         !< basale hydro. conductivity 'o' 
    169   real,dimension(nx,ny) :: PDD          !< Positive degree day 
    170   real,dimension(nx,ny) :: PRECIP       !< precipitation 
    171   real,dimension(nx,ny) :: PRECIP0      !< initial precipitation  (used in 'heminord') 
     139 
    172140  real,dimension(nx,ny) :: PHID         !< flux de chaleur lie a la deformation et glissement basal 
    173   real,dimension(nx,ny) :: PWATER       !< basal water pressure 
    174   real,dimension(nx,ny) :: pgx,pgy      !< hydro. potential gradient  / x '>' and / y '^' 
    175   real,dimension(nx,ny) :: phiWx,phiWy  !< flux d'eau sous glaciaire  / x '>' and / y '^' 
    176141  real,dimension(nx,ny) :: NEFFMX       !< pression effective '>' 
    177142  real,dimension(nx,ny) :: NEFFMY       !< pression effective '^' 
    178143  real,dimension(nx,ny) :: TOBMX        !< cisaillement basal '>' 
    179144  real,dimension(nx,ny) :: TOBMY        !< cisaillement basal '^' 
    180   real,dimension(nx,ny) :: SW           !< for bedrock isostasy 
    181145  double precision,dimension(nx,ny) :: S            !< altitude of ice sheet surface 
    182146  real,dimension(nx,ny) :: sealevel_2d  !< local sea surface elevation 
     
    184148  real,dimension(nx,ny) :: SDX          !< slope derivee / x '>' 
    185149  real,dimension(nx,ny) :: SDY          !< slope derivee / y '^' 
    186   real,dimension(nx,ny) :: SDXMY        !< slope selon x moy selon y '^' remplace SDMX 
    187   real,dimension(nx,ny) :: SDYMX        !< slope selon y moy selon x '>' remplace SDMY 
    188150  real,dimension(nx,ny) :: SLOPE2mx     !< = Sdx**2 + Sdymx**2 '>' 
    189151  real,dimension(nx,ny) :: SLOPE2my     !< = Sdy**2 + Sdxmy**2 '^' 
     
    193155  real,dimension(nx,ny) :: TANN         !< Ground air temperature annual 
    194156  real,dimension(nx,ny,12) :: Tmois        !< Ground air temperature monthly 
    195   real,dimension(nx,ny) :: TSHELF       !< temperature des shelfs pour viscosite 
    196   real,dimension(nx,ny) :: TJ0          !< initial air temperature at sea level July 
    197 !  real,dimension(nx,ny) :: TA0          !< initial air temperature at sea level annual 
    198157  real,dimension(nx,ny) :: TAUB         !< basal shear stress (for output) 
    199158  real,dimension(nx,ny) :: TAUSHELF     !< effective stress in ice shelves (vertical av.)  
    200159  real,dimension(nx,ny) :: TS           !< surface ice temperature  'o' 
    201160  real,dimension(nx,ny) :: TB           !< basal ice temperature  'o' 
    202   real,dimension(nx,ny) :: TG           !< degrees above melting point at the base 
    203161  real,dimension(nx,ny) :: TBDOT        !< variation in time of basal temperature  
    204162  real,dimension(nx,ny) :: UZK          !< vertical velocity at the ice surface (kinematic boundary) 
     
    212170  real,dimension(nx,ny) :: UBY          !< basal sliding '^' 
    213171  real,dimension(nx,ny) :: UZSDOT       !< variation in time of surface vertical velocity  
    214   real,dimension(nx,ny) :: UX1          !<  
    215   real,dimension(nx,ny) :: UY1          !<  
    216   real,dimension(nx,ny) :: VBAR         !< depth averaged velocity magnitude (for output) 
    217 !!!!!!!real,dimension(nx,ny) :: VSDOT        ! variation in time of surface velocity magnitude  
    218   real,dimension(nx,ny) :: W0           !< enfoncement du socle a l'equilibre isostatique 
    219   real,dimension(nx,ny) :: W1           !< enfoncement du socle courant 
    220172  real,dimension(nx,ny) :: XLONG        !< longitude 
    221173  real,dimension(nx,ny) :: YLAT         !< latitude 
    222174  real,dimension(nx,ny) :: xcc          ! grille Xkm 
    223175  real,dimension(nx,ny) :: ycc          ! grille Ykm 
    224 !  real,dimension(nx,ny) :: ZS           !< surface topography above sea level 
    225   real,dimension(nx,ny) :: ETABAR       !<  
    226176  real,dimension(nx,ny) :: BSOC         !< altitude (ou bathymetrie) du socle 'o' 
    227177  real,dimension(nx,ny) :: PVI          !< viscosite ice shelf 
    228178  real,dimension(nx,ny) :: PVM          !< viscosite ice shelf 
    229   real,dimension(nx,ny) :: ramollo      !< pour ramollir les ice shelves 
    230179  real,dimension(nx,ny) :: Abar         !< coefficient de Glen integre 
    231   real,dimension(nx,ny) :: Uiter_centre !< pour iterations equation diagnostique 
    232   real,dimension(nx,ny) :: tabtest      !< tableau de travail 
    233180 
    234181 
     
    241188  integer,dimension(nx,ny) :: mstream_my  !< masque stream selon y 
    242189  integer,dimension(nx,ny) :: mstream     !< masque stream sur les noeuds majeurs 
    243   real,dimension(nx,ny) :: socle_cry      !< courbure du socle, negatif -> vallees 
    244190  real,dimension(nx,ny) :: drag_mx        !< coefficient pour tenir compte de variations         
    245191  real,dimension(nx,ny) :: drag_my        !< geographiques eventuelles dans le basal drag 
    246192 
    247   integer,dimension(nx,ny) :: mslid_mx    !< masque glissement selon x 
    248   integer,dimension(nx,ny) :: mslid_my    !< masque glissement selon y 
    249   real,dimension(nx,ny) :: slid_mx        !< coefficient pour tenir compte de variations         
    250   real,dimension(nx,ny) :: slid_my        !< geographiques eventuelles dans le glissement 
    251  
    252  
    253  
    254   !REAL,dimension(-NL:NL,-NL:NL) :: WE   ! enfoncement du socle autour d'une charge unitaire 
    255  
    256  
    257  
    258193  !      ********** common des tableaux a 3 dimensions ***** 
    259   !real,dimension(:,:,:,:),allocatable :: BTT !< deformation parameter for flow law  
    260  
    261   !real,dimension(:,:,:,:),allocatable :: SA ! effet temperature sur la deformation (loi n=3) 
    262   !real,dimension(:,:,:,:),allocatable :: S2A ! effet integre sur l'epaisseur temperature sur la deformation (loi n=3) 
    263   !real,dimension(:,:,:,:),allocatable :: SA_mx ! effet temperature sur la deformation (loi n=3) 
    264   !real,dimension(:,:,:,:),allocatable :: S2A_mx ! effet integre sur l'epaisseur temperature sur la deformation (loi n=3) 
    265  
    266   !real,dimension(:,:,:,:),allocatable :: SA_my ! effet temperature sur la deformation (loi n=3) 
    267   !real,dimension(:,:,:,:),allocatable :: S2A_my ! effet integre sur l'epaisseur temperature sur la deformation (loi n=3) 
     194 
    268195  real,dimension(nx,ny,nz) :: SUX       !<  
    269196  real,dimension(nx,ny,nz) :: SUY       !<  
     
    299226  ! ===================== Booleens ======================================== 
    300227  logical :: SHELFY                     !<  
    301   logical :: BOOST                      !<  
    302228  logical :: MARINE                     !<  
    303   logical :: appel_new_flot             !< pour appeler la routine new_flot 
    304229 
    305230  logical,dimension(nx,ny) :: FLOT      !< vrai si flottant (test d'archimede) 'o' 
     
    308233  logical,dimension(nx,ny) :: FRONT_RESC!< comme front (mais boolean) pour remplimat rescue 
    309234  logical,dimension(nx,ny) :: FBM       !<  
    310   logical,dimension(nx,ny) :: OKUMAT    !<  
    311   logical,dimension(nx,ny) :: OKVMAT    !<  
    312   logical,dimension(nx,ny) :: GRZONE    !<  
    313235  logical,dimension(nx,ny) :: GZMX      !< point stream ">" 
    314236  logical,dimension(nx,ny) :: GZMY      !< point stream "^" 
     
    317239  logical,dimension(nx,ny) :: ILEMX     !< points ile ">" 
    318240  logical,dimension(nx,ny) :: ILEMY     !< points ile "^" 
    319   logical,dimension(nx,ny) :: cotemx    !< points cotiers ">" 
    320   logical,dimension(nx,ny) :: cotemy    !< points cotiers "^" 
    321241  logical,dimension(nx,ny) :: fleuvemx  !< actual grounded stream 
    322242  logical,dimension(nx,ny) :: fleuvemy  !< actual grounded stream 
    323   logical,dimension(nx,ny) :: isolx     !< designe un point sans voisin sur ses faces x 
    324   logical,dimension(nx,ny) :: isoly     !< designe un point sans voisin sur ses faces y 
    325   logical,dimension(nx,ny) :: new_flot_point  !< pour signaler les points qui se mettent a flotter entre 2 pas de temps dtt 
    326   logical,dimension(nx,ny) :: new_flotmx !< pour signaler les points qui deviennent flottantmx entre 2 dtt  
    327   logical,dimension(nx,ny) :: new_flotmy !< pour signaler les points qui deviennent flottantmy entre 2 dtt  
    328243  logical,dimension(nx,ny) :: flot_marais  !< afq -- vrai si flottant et coince entre points poses 'o' 
    329244  logical,dimension(nx,ny) :: iceberg   !< point iceberg 
     
    359274  integer :: num_file4     = 995  !< Id of  
    360275  integer :: num_coor      = 2004 !< Id of coord-Ant-40km 
    361 !  integer :: num_tracebug        !< numero de l'unite itracebug 
    362276 
    363277  ! Variables communes au main et aux subroutines du step 
    364   logical :: base_froide 
    365   logical :: base_temp 
    366278  real  :: timemax 
    367279 
  • branches/GRISLIv3/SOURCES/Climate_modules/climat-perturb_mod-0.4.f90

    r451 r467  
    1313 
    1414 
    15 use module3d_phy,only: S,S0,Tann,Tjuly,precip,acc,Ylat,num_forc,num_param,num_rep_42,tafor,time,sealevel,sealevel_2d,coefbmshelf 
     15use module3d_phy,only: S,S0,Tann,Tjuly,acc,Ylat,num_forc,num_param,num_rep_42,tafor,time,sealevel,sealevel_2d,coefbmshelf 
    1616use geography, only: nx,ny,dirforcage,dirnameinp 
    1717use io_netcdf_grisli, only: read_ncdf_var 
     
    2525 
    2626real,dimension(nx,ny) :: ta0          !< initial air temperature at sea level annual 
     27real,dimension(nx,ny) :: precip 
    2728 
    2829real :: coefT                   !< pour modifier l'amplitude de la perturb. T 
  • branches/GRISLIv3/SOURCES/Netcdf-routines/sortie_netcdf_GRISLI_mod.0.2-hassine.f90

    r449 r467  
    665665    use geography,    only: nx,ny,nz,nzm,dx,dy 
    666666    use runparam,     only: itracebug,xmin,ymin,dirsource 
    667     use module3d_phy, only: s,s0,h,h0,b,socle_cry,sealevel,mk,mk_init,hdot,dhdt,tann,tjuly,t,tpmp, & 
     667    use module3d_phy, only: s,s0,h,h0,b,sealevel,mk,mk_init,hdot,dhdt,tann,tjuly,t,tpmp, & 
    668668                            acc,abl,ghf,phid,bmelt,uxbar,uybar,ux,uy,frotmx,frotmy,tobmx,tobmy,    & 
    669669                            taushelf,epsxx,epsyy,epsxy,eps,abar,pvi,pvm,betamx,betamy,beta_centre, & 
    670                             ablbord_dtt,ice,front,gr_line_schoof,hwater,hdotwater,kond,bsoc,bm,    & 
    671                             pgx,pgy,phiwx,phiwy,flot_marais,neffmx,neffmy,gzmx,gzmy,ilemx,ilemy,   & 
    672                             fleuvemx,fleuvemy,flotmx,flotmy,hmx,hmy,frontfacex,frontfacey,sux,suy, & 
     670                            ablbord_dtt,ice,front,gr_line_schoof,hwater,hdotwater,bsoc,bm,    & 
     671                            flot_marais,neffmx,neffmy,gzmx,gzmy,ilemx,ilemy,   & 
     672                            fleuvemx,fleuvemy,flotmx,flotmy,hmx,hmy,sux,suy, & 
    673673                            tpmp,ux,uy,uzr,debug_3d,xlong,ylat,time,dtt 
     674    use eau_basale, only: kond,pgx,pgy,phiwx,phiwy 
    674675    use tracer_vars,  only: xdep_out,ydep_out,tdep_out 
    675676    use bilan_eau_mod,only: tot_water,calv_dtt 
     
    788789                   tab(:,:) = b(:,:) 
    789790                end if 
    790                 if (itab.eq.8) then 
    791                    tab(:,:) = socle_cry(:,:) 
    792                 end if 
     791                !if (itab.eq.8) then 
     792                !   tab(:,:) = socle_cry(:,:)  !no longer computed 
     793                !end if 
    793794                if (itab.eq.9) then 
    794795                   tab(:,:) = mk_init(:,:) 
     
    10151016                   end do 
    10161017                end if 
    1017                 if (itab.eq.72) then  
    1018                    tab(:,:) = frontfacex(:,:) 
    1019                 end if 
    1020                 if (itab.eq.73) then  
    1021                    tab(:,:) = frontfacey(:,:) 
    1022                 end if 
     1018                !if (itab.eq.72) then !no longer computed 
     1019                !   tab(:,:) = frontfacex(:,:) 
     1020                !end if 
     1021                !if (itab.eq.73) then  
     1022                !   tab(:,:) = frontfacey(:,:) 
     1023                !end if 
    10231024 
    10241025                !SORTIE 3D  
  • branches/GRISLIv3/SOURCES/New-remplimat/diagno-L2_mod.f90

    r446 r467  
    66implicit none 
    77 
    8  
     8real ::  pvimin                       !< valeur de pvi pour les noeuds fictifs 
    99 
    1010real                   :: somint,test,delp,prec 
     
    1212real, dimension(nx,ny) :: uyb1 
    1313 
     14real, dimension(nx,ny) :: ramollo      !< pour ramollir les ice shelves 
    1415real, dimension(nx,ny) :: uxb1ramollo 
    1516real, dimension(nx,ny) :: uyb1ramollo 
     
    4950subroutine init_diagno 
    5051 
    51 use module3D_phy,only: num_rep_42,num_param,pvimin 
     52use module3D_phy,only: num_rep_42,num_param 
    5253use geography, only: geoplace 
    5354use deformation_mod_2lois,only: sf ! afq - 07/2023 - not clean since it is in module_choix 
     
    111112 
    112113  use module3D_phy, only: niter_nolin,taushelf,flot,h,pvi, &  
    113                           gr_line_schoof,uxbar,uybar,pvimin,debug_3D,V_limit, &  
     114                          gr_line_schoof,uxbar,uybar,debug_3D,V_limit, &  
    114115                          imx_diag,imy_diag,tobmx,tobmy,neffmx,neffmy,gr_line, schoof, &  
    115116                          betamx,betamy,flgzmx,flgzmy,uxflgz,uyflgz,taub  
     
    378379subroutine calc_pvi 
    379380 
    380 use module3d_phy, only: pvi,pvimin,abar,flot,gzmx,gzmy, &  
    381                         ilemx,ilemy,eps,taushelf,h,ramollo,debug_3d,pvm 
     381use module3d_phy, only: pvi,abar,flot,gzmx,gzmy, &  
     382                        ilemx,ilemy,eps,taushelf,h,debug_3d,pvm 
    382383use runparam, only: itracebug 
    383384use geography, only: nx,ny,nz 
  • branches/GRISLIv3/SOURCES/New-remplimat/remplimat-shelves-tabTu.f90

    r446 r467  
    4444use module3d_phy, only: debug_3D,hmx,hmy,pvi,  & 
    4545                        flgzmx,flgzmy,frotmx,frotmy,betamx,betamy,betamax,betamax_2d, & 
    46                         sdx,sdy,h,b,pvimin,sealevel_2d,flotmx,flotmy,drag_mx,drag_my, & 
     46                        sdx,sdy,h,b,sealevel_2d,flotmx,flotmy,drag_mx,drag_my, & 
    4747                        beta_centre,pvm 
    4848use runparam, only: itracebug,num_tracebug 
     
    11101110! et qui ne dépendent d'aucun noeud (ligne Tu,Tv nulle sauf diagonale) 
    11111111 
     1112use diagno_mod, only: pvimin 
     1113 
    11121114implicit none 
    11131115 
  • branches/GRISLIv3/SOURCES/Temperature-routines/icetemp_mod.f90

    r446 r467  
    7070  subroutine icetemp 
    7171    !$ use OMP_LIB  
    72     use module3D_phy, only: uxbar,uybar,dtt,nzm,time,ux,uy,uzr,ts,h,h1,b,b1, & 
     72    use module3D_phy, only: uxbar,uybar,dtt,nzm,time,ux,uy,uzr,ts,h,b, & 
    7373                             ghf,t,tpmp,phid,flot,ibase,debug_3D,tbdot 
    7474    use runparam, only: itracebug,num_tracebug 
     
    223223    Do J=1,Ny 
    224224       Do I=1,Nx 
    225           H1(I,J)=H(I,J) 
    226           B1(I,J)=B(I,J) 
    227225          Tpmp(I,J,1)=0. 
    228226       End Do 
  • branches/GRISLIv3/SOURCES/ablation_mod.f90

    r465 r467  
    8484 
    8585 
    86   use module3d_phy,only:Tjuly,Tann,Tmois,acc,pdd,TS,Tshelf,precip,BM,Abl,S 
     86  use module3d_phy,only:Tjuly,Tann,Tmois,acc,TS,BM,Abl,S 
    8787  use param_phy_mod,only:dice,cl 
    8888 
    8989  IMPLICIT NONE 
    9090 
    91   real, dimension(nx,ny) :: pds, simax, pdsi, sif 
     91  real, dimension(nx,ny) :: precip, pdd, pds, simax, pdsi, sif 
    9292  integer :: i,j,k,mo,nday 
    9393  real :: summ 
     
    285285  TS(:,:)=(TANN(:,:)+26.6*SIF(:,:)) 
    286286  TS(:,:)=min(0.0,TS(:,:)) 
    287   tshelf(:,:)=TS(:,:) 
    288287  Abl(:,:)=BM(:,:)-Acc(:,:) 
    289288 
  • branches/GRISLIv3/SOURCES/conserv-mass-adv-diff_sept2009_mod.f90

    r446 r467  
    1919module equat_adv_diff_2D_vect                          ! Cat nouvelle mouture juin 2009 
    2020  use module3D_phy, only: V_limit,num_param,num_rep_42,dx1,mk0,i_Hp,Hp,H,uxbar,uybar,testdiag,& 
    21        dtmax,dt,dtmin,time,dtt,isynchro,diffmx,diffmy,sdx,sdy,hmx,hmy,flgzmx,flgzmy,flot,tabtest,timemax,& 
     21       dtmax,dt,dtmin,time,dtt,isynchro,diffmx,diffmy,sdx,sdy,hmx,hmy,flgzmx,flgzmy,flot,timemax,& 
    2222       marine,dtdx2,dtdx,bm,bmelt,igrdline,ibmelt_inv,ice,ablbord,hdot 
    2323  use geography, only: nx,ny,dx,geoplace 
     
    8989    implicit none 
    9090    integer :: i,j 
     91    real,dimension(nx,ny) :: tabtest      ! tableau de travail 
    9192    real,dimension(nx,ny) :: Dminx,Dminy 
    9293    real,dimension(nx,ny) :: Uxdiff,Uydiff           ! vitesse due a la diffusion 
  • branches/GRISLIv3/SOURCES/eaubasale-0.5_mod.f90

    r465 r467  
    3434  real :: nefflocal 
    3535 
     36  real,dimension(nx,ny) :: KOND         !< basale hydro. conductivity 'o' 
     37  real,dimension(nx,ny) :: pgx,pgy      !< hydro. potential gradient  / x '>' and / y '^' 
     38  real,dimension(nx,ny) :: phiWx,phiWy  !< flux d'eau sous glaciaire  / x '>' and / y '^' 
     39  real,dimension(nx,ny) :: PWATER       !< basal water pressure 
    3640  REAL,dimension(NX,NY) :: limit_hw    !< conditions aux limites 
    3741  integer,dimension(NX,NY) :: klimit    !< ou appliquer les conditions  
     
    5761  subroutine init_eaubasale 
    5862 
    59     use module3d_phy, only:num_param,num_rep_42,kond,secyear,hdotwater,pgx,pgy 
     63    use module3d_phy, only:num_param,num_rep_42,secyear,hdotwater 
    6064     
    6165    namelist/eaubasale1/ecoulement_eau,hwatermax,infiltr  
     
    126130  subroutine eaubasale !(pwater)   version correspondant à la thèse de Vincent 
    127131 
    128     use module3d_phy, only:hwater,kond,secyear,flot,sealevel_2D,Bsoc,ibase,S,H,B,bmelt,& 
    129          debug_3d,flotmx,flotmy,pgx,pgy,phiwx,phiwy,isynchro,dtt,dt,hdotwater,pwater 
     132    use module3d_phy, only:hwater,secyear,flot,sealevel_2D,Bsoc,ibase,S,H,B,bmelt,& 
     133         debug_3d,flotmx,flotmy,isynchro,dtt,dt,hdotwater 
    130134    use geography, only:dx,dy 
    131135    use param_phy_mod, only:rowg,ro,rog,rofreshg,rofresh 
  • branches/GRISLIv3/SOURCES/flottab2-0.7.f90

    r446 r467  
    104104     
    105105    use runparam, only:itracebug,nt 
    106     use module3D_phy, only:shelfy,igrdline,mk_init,flot,H,sealevel_2d,Bsoc,S,H,B,appel_new_flot,& 
    107          new_flot_point,new_flotmx,new_flotmy,ice,front,frontfacex,frontfacey,isolx,isoly,cotemx,& 
    108          cotemy,boost,iceberg,uxbar,uybar,mk,gzmx,gzmy,flotmx,flotmy,hmx,hmy,isynchro,ilemx,ilemy,& 
     106    use module3D_phy, only:shelfy,igrdline,mk_init,flot,H,sealevel_2d,Bsoc,S,H,B,& 
     107         ice,front,& 
     108         iceberg,uxbar,uybar,mk,gzmx,gzmy,flotmx,flotmy,hmx,hmy,isynchro,ilemx,ilemy,& 
    109109         flgzmx,flgzmy,marine,fbm,bm,bmelt,debug_3D,dt 
    110110    use param_phy_mod, only:row,ro 
     
    113113    implicit none 
    114114     
     115    logical,dimension(nx,ny) :: new_flot_point  !< pour signaler les points qui se mettent a flotter entre 2 pas de temps dtt 
     116    logical,dimension(nx,ny) :: new_flotmx !< pour signaler les points qui deviennent flottantmx entre 2 dtt 
     117    logical,dimension(nx,ny) :: new_flotmy !< pour signaler les points qui deviennent flottantmy entre 2 dtt  
     118 
    115119    integer :: i,j 
    116120     
     
    141145    ! a flotter entre 2 dtt 
    142146 
    143     appel_new_flot=.false. 
    144147    !$OMP DO 
    145148    do j=1,ny 
     
    157160    ICE(:,:)=0 
    158161    front(:,:)=0 
    159     frontfacex(:,:)=0 
    160     frontfacey(:,:)=0 
    161     isolx(:,:)=.false. 
    162     isoly(:,:)=.false. 
    163     cotemx(:,:)=.false. 
    164     cotemy(:,:)=.false. 
    165     boost=.false. 
    166162    iceberg(:,:)=.false. 
    167163    !$OMP END WORKSHARE 
     
    190186             ex_pose: if ((.not.FLOT(I,J)).and.(isynchro.eq.1)) then  !  il ne flottait pas avant 
    191187                FLOT(I,J)=.true. 
    192                 BOOST=.false. 
    193188 
    194189                if (igrdline.eq.1) then   ! en cas de grounding line prescrite 
     
    220215             if(FLOT(I,J)) then         !  mais il flottait avant 
    221216                FLOT(I,J)=.false. 
    222                 BOOST=.false. 
    223217             endif 
    224218             !cdc correction topo pour suivre  variations sealevel 
     
    283277          if (flotmx(i,j).and.(new_flot_point(i,j).or. & 
    284278               new_flot_point(i-1,j))) then 
    285              appel_new_flot=.true. 
    286              new_flotmx(i,j)=.true. 
     279               new_flotmx(i,j)=.true. 
    287280          endif 
    288281 
     
    301294          archim=(Bsoc(i,j)+Bsoc(i-1,j))*0.5-(sealevel_2d(i,j)+sealevel_2d(i-1,j))*0.5+ro/row*Hmx(i,j) 
    302295          gzmx(i,j)=gzmx(i,j).and.(archim.le.100.)  
    303           cotemx(i,j)=gzmx(i,j) 
    304296 
    305297       end do 
     
    323315          if (flotmy(i,j).and.(new_flot_point(i,j).or.     & 
    324316               new_flot_point(i,j-1))) then 
    325              appel_new_flot=.true. 
    326              new_flotmy(i,j)=.true. 
     317               new_flotmy(i,j)=.true. 
    327318          endif 
    328319 
     
    339330 
    340331          archim=(Bsoc(i,j)+Bsoc(i,j-1))*0.5-(sealevel_2d(i,j)+sealevel_2d(i,j-1))*0.5+ro/row*Hmy(i,j) 
    341           gzmy(i,j)=gzmy(i,j).and.(archim.le.100.)  
    342           cotemy(i,j)=gzmy(i,j) 
     332          gzmy(i,j)=gzmy(i,j).and.(archim.le.100.) 
    343333 
    344334       end do 
     
    820810  subroutine determin_front 
    821811 
    822     use module3D_phy, only:ice,H,front,frontfacex,frontfacey,isolx,isoly 
     812    use module3D_phy, only:ice,H,front 
    823813 
    824814     
     
    10391029    !$OMP END DO 
    10401030 
    1041     !isolx signifie pas de voisins en x 
    1042     !isoly signifie pas de voisins en y 
    1043     !remarque :  
    1044     !si isolx/y=.true. alors frontfacex/y=0 (a la fois +1 & -1 or +1-1=0) 
    1045  
    1046     ! calcul de frontfacex et isolx 
    1047     !$OMP DO 
    1048     do j=1,ny 
    1049        do i=2,nx-1 
    1050  
    1051           if (front(i,j).ge.1.and.front(i,j).le.3) then    !front(entre 1 et 3) 
    1052  
    1053              if ((ice(i-1,j)+ice(i+1,j)).lt.2) then        ! il y a un front // a x 
    1054  
    1055                 if ((ice(i-1,j)+ice(i+1,j)).eq.0) then 
    1056                    isolx(i,j)=.true. 
    1057                 elseif (ice(i-1,j).eq.0) then 
    1058                    frontfacex(i,j)=-1                      ! front  i-1 |i  i+1 
    1059                 else 
    1060                    frontfacex(i,j)=+1                      ! front  i-1  i| i+1 
    1061                 endif 
    1062              endif 
    1063           end if !fin du test il y a un front 
    1064  
    1065        end do 
    1066     end do 
    1067     !$OMP END DO 
    1068  
    1069     ! calcul de frontfacey et isoly 
    1070     !$OMP DO 
    1071     do j=2,ny-1 
    1072        do i=1,nx 
    1073  
    1074           if (front(i,j).ge.1.and.front(i,j).le.3) then   !front(entre 1 et 3) 
    1075  
    1076              if ((ice(i,j-1)+ice(i,j+1)).lt.2) then       ! il y a un front // a y 
    1077  
    1078                 if ((ice(i,j-1)+ice(i,j+1)).eq.0) then 
    1079                    isoly(i,j)=.true.                      !front   j-1 |j| j+1 
    1080                 elseif (ice(i,j-1).eq.0) then 
    1081                    frontfacey(i,j)=-1                     !front   j-1 |j j+1 
    1082                 else 
    1083                    frontfacey(i,j)=+1                     !front   j-1  j| j+1 
    1084                 endif 
    1085              endif 
    1086           end if !fin du test il y a un front 
    1087  
    1088        end do 
    1089     end do 
    1090     !$OMP END DO 
    1091  
    1092  
    1093     ! traitement des bords. On considere que l'exterieur n'a pas de glace 
    1094     ! attention ce n'est vrai que sur la grande grille 
    1095  
    1096     !$OMP DO PRIVATE(i) 
    1097     do j=2,ny-1 
    1098        i=1 
    1099        if (front(i,j).ge.1)  then  
    1100           if (ice(i+1,j).eq.0) then  
    1101              isolx(i,j)=.true. 
    1102           else 
    1103              frontfacex(i,j)=-1 
    1104           endif 
    1105        end if 
    1106        i=nx 
    1107        if (front(i,j).ge.1)  then  
    1108           if (ice(i-1,j).eq.0) then  
    1109              isolx(i,j)=.true. 
    1110           else 
    1111              frontfacex(i,j)=1 
    1112           endif 
    1113        end if 
    1114     end do 
    1115     !$OMP END DO 
    1116  
    1117     !$OMP DO PRIVATE(j) 
    1118     do i=2,nx-1 
    1119        j=1  
    1120        if (front(i,j).ge.1)  then  
    1121           if (ice(i,j+1).eq.0) then  
    1122              isoly(i,j)=.true. 
    1123           else 
    1124              frontfacey(i,j)=-1 
    1125           endif 
    1126        end if 
    1127        j=ny 
    1128        if (front(i,j).ge.1)  then  
    1129           if (ice(i,j-1).eq.0) then  
    1130              isoly(i,j)=.true. 
    1131           else 
    1132              frontfacey(i,j)=1 
    1133           endif 
    1134        end if 
    1135     end do 
    1136     !$OMP END DO 
    11371031    !$OMP END PARALLEL 
    11381032 
  • branches/GRISLIv3/SOURCES/initial2-0.4.f90

    r446 r467  
    1717subroutine INITIAL2() 
    1818 
    19   USE module3D_phy, only: cde,abl,bdot,bmelt,epsxx,epsyy,epsxy,hwater,calv,hdot,hdotwater,pdd, & 
    20                     slope,taub,tg,ubx,uby,uzk,uxbar,uybar,vbar,ibase,tpmp,mk,mk0,h,grzone,front, & 
    21                     frontfacex,frontfacey,bsoc,flot,sealevel_2D,flotmx,flotmy,okumat,okvmat,gzmx, & 
     19  USE module3D_phy, only: cde,abl,bdot,bmelt,epsxx,epsyy,epsxy,hwater,calv,hdot,hdotwater, & 
     20                    slope,taub,ubx,uby,uzk,uxbar,uybar,ibase,tpmp,mk,mk0,h,front, & 
     21                    bsoc,flot,sealevel_2D,flotmx,flotmy,gzmx, & 
    2222                    gzmy,flgzmx,flgzmy,ilemx,ilemy,sdx,sdy,ux,uy,uzr,t,s 
    2323  use geography, only: nx,ny,nz,nzm,dx 
    24   USE param_phy_mod 
     24  USE param_phy_mod,only: ro,row 
    2525  implicit none 
    2626  real,dimension(NZ) ::cord_vert  
     
    4747  HDOT(:,:)=0.  
    4848  HDOTWATER(:,:)=0. 
    49   PDD(:,:)=0. 
    5049  SLOPE(:,:)=0.  
    5150  TAUB(:,:)=0.  
    52   TG(:,:)=0. 
    5351  UBX(:,:)=0. 
    5452  UBY(:,:)=0. 
     
    5654  UXBAR(:,:)=0. 
    5755  UYBAR(:,:)=0. 
    58   VBAR(:,:)=0. 
    5956  IBASE(:,:)=1 
    6057  TPMP(:,:,1)=0 
     
    6259 
    6360  MK(:,:)=MK0(:,:) 
    64   grzone(:,:)=.false. 
    6561 
    6662 
    6763  !-------Initialisation des fronts. 
    6864  FRONT(:,:)  =0  
    69   FRONTFACEX(:,:)=0 
    70   FRONTFACEY(:,:)=0 
    7165 
    7266  !-------Initialisation des flot... devrait etre mise dans input_topo. 
     
    8680  FLOTMX(:,:)=FLOT(:,:) 
    8781  FLOTMY(:,:)=FLOT(:,:) 
    88   OKUMAT(:,:)=.FALSE. 
    89   OKVMAT(:,:)=.FALSE. 
    9082  GZMX(:,:)=.FALSE. 
    9183  GZMY(:,:)=.FALSE. 
  • branches/GRISLIv3/SOURCES/isostasie_mod-0.3.f90

    r465 r467  
    1616 
    1717module isostasie_mod 
    18   
     18 
     19   use geography, only: nx,ny  
    1920   use iso_declar,only: nbed  
     21 
     22   implicit none 
     23 
     24   real,dimension(nx,ny) :: W0           !< enfoncement du socle a l'equilibre isostatique 
     25   real,dimension(nx,ny) :: W1           !< enfoncement du socle courant 
    2026 
    2127contains 
     
    2733 
    2834    use iso_declar,only: nlith,dt_iso,tausoc,dl,rl,lbloc,we,charge 
    29     use module3D_phy, only: icouple,marine,err,h0,bsoc0,sealevel_2d,w0,w1 
     35    use module3D_phy, only: icouple,marine,err,h0,bsoc0,sealevel_2d 
    3036    use geography, only: geoplace,nx,ny,dx,dy 
    3137    use param_phy_mod, only: ro,row,rog,rowg,romg 
  • branches/GRISLIv3/SOURCES/lineartemp-0.2.f90

    r414 r467  
    1313 
    1414  use geography, only:nx,ny,nz,nzm 
    15   use module3D_phy, only:H1,H,B1,B,TG,bmelt,T,TS,tpmp,ghf 
     15  use module3D_phy, only:H,B,bmelt,T,TS,tpmp,ghf 
    1616  use icetemp_declar, only:Dzm,Cm 
    1717   
     
    1919 
    2020  integer :: i,j,k 
     21  real,dimension(nx,ny) :: TG           !< degrees above melting point at the base 
    2122 
    2223  do I=1,NX 
    2324     do J=1,NY  
    24         H1(I,J)=H(I,J)  
    25         B1(I,J)=B(I,J)  
    2625        TG(I,J)=0. 
    2726        BMELT(I,J)=0. 
  • branches/GRISLIv3/SOURCES/litho-0.4.f90

    r446 r467  
    3939subroutine litho 
    4040  !$ USE OMP_LIB 
    41   USE module3D_phy, only: err,w1 
     41  USE module3D_phy, only: err 
    4242  use geography, only: nx,ny 
     43  use isostasie_mod, only: w1 
    4344  USE iso_declar, only: lbloc,we,charge ! module de declaration des variables specifiques a l'isostasie 
    4445 
  • branches/GRISLIv3/SOURCES/main3D-0.4-40km.f90

    r465 r467  
    133133  USE module3D_phy, only: itemp,icouple,isynchro,icompteur,iglen,marine,num_sealevel, & 
    134134                          num_ts_ritz,num_ic_vo,num_ic_by,num_ic_dm,num_ic_dc,num_ic_df, & 
    135                           s,h,b,bsoc,flot,mk,mk0,uxbar,uybar,hwater,time,timemax,boost,ndebug,ndebug_max 
     135                          s,h,b,bsoc,flot,mk,mk0,uxbar,uybar,hwater,time,timemax,ndebug,ndebug_max 
    136136  use runparam, only: nt,tbegin,tgrounded,dtprofile,dtcpt,dirnameout,runname,itracebug 
    137137  use geography, only: nx,ny,geoplace 
     
    349349  endif 
    350350 
    351   boost = .false. 
    352  
    353351  do i=2,nx-1 
    354352     do j=2,ny-1 
  • branches/GRISLIv3/SOURCES/prescribe-H-i2s_mod.f90

    r431 r467  
    2121  !  use toy_retreat_mod 
    2222 
     23  use geography,only: nx,ny 
     24 
    2325  implicit none 
    2426  !  real,dimension(nx,ny)    :: Hp           !< H value if prescribed 
     
    2830  !  integer,dimension(nx,ny) :: i_Hp         !< 1 if H is prescribed on this node, else 0 
    2931  !  integer,dimension(nx,ny) :: i_Hp0        !< i_hp mask reference value does not change with time 
    30   !  integer,dimension(nx,ny) :: MK_gl0       !< mask grounding line initial 
    31   !  integer,dimension(nx,ny) :: MK_flot0     !< mask float initial 
     32    integer,dimension(nx,ny) :: MK_gl0       !< mask grounding line initial 
     33    integer,dimension(nx,ny) :: MK_flot0     !< mask float initial 
    3234 
    3335  ! pour grounding line retreat, ice2sea 
     
    4850  subroutine init_prescribe_H 
    4951 
    50     use module3D_phy, only: flot,MK_flot0,MK_gl0,Hp0,H0,Mk_init,i_hp0 
     52    use module3D_phy, only: flot,Hp0,H0,Mk_init,i_hp0 
    5153    use geography, only: nx,ny,geoplace 
    5254    use runparam, only: itracebug  
     
    103105  subroutine prescribe_present_H_gl 
    104106     
    105     use module3D_phy, only: MK_flot0,MK_gl0,i_hp,Hp,Hp0 
     107    use module3D_phy, only: i_hp,Hp,Hp0 
    106108    use runparam, only: itracebug  
    107109     
     
    170172  subroutine prescribe_paleo_gl_shelf 
    171173     
    172     use module3D_phy, only: MK_flot0,MK_gl0,i_hp,hp,sealevel_2d,Bsoc 
     174    use module3D_phy, only: i_hp,hp,sealevel_2d,Bsoc 
    173175    use runparam, only: itracebug  
    174176    use param_phy_mod, only: row,ro 
     
    245247  subroutine break_all_ice_shelves 
    246248     
    247     use module3D_phy, only: i_hp,hp,hp0,H,debug_3D,flot,MK_flot0 
     249    use module3D_phy, only: i_hp,hp,hp0,H,debug_3D,flot 
    248250    use runparam, only: itracebug 
    249251     
     
    336338  subroutine prescribe_present_H_gl_copy 
    337339     
    338     use module3D_phy, only: i_hp,hp,Hp0,MK_flot0,MK_gl0 
     340    use module3D_phy, only: i_hp,hp,Hp0 
    339341    use runparam, only: itracebug  
    340342    use geography, only: nx,ny 
  • branches/GRISLIv3/SOURCES/slope_surf.f90

    r428 r467  
    1313subroutine slope_surf 
    1414 
    15   use module3D_phy, only: sdx,sdy,S,slope,sdxmy,sdymx,slope2mx,slope2my,debug_3D 
     15  use module3D_phy, only: sdx,sdy,S,slope,slope2mx,slope2my,debug_3D 
    1616  use geography, only: nx,ny,dx,dy 
    1717  !$ USE OMP_LIB 
    1818   
    1919  implicit none 
     20 
     21  real,dimension(nx,ny) :: SDXMY        !< slope selon x moy selon y '^' remplace SDMX 
     22  real,dimension(nx,ny) :: SDYMX        !< slope selon y moy selon x '>' remplace SDMY 
    2023 
    2124  real :: inv_4dx        ! inverse de dx pour eviter les divisions =1/(4*dx) 
  • branches/GRISLIv3/SOURCES/spinup_mod.f90

    r446 r467  
    682682  subroutine ajust_ghf 
    683683     
    684     use module3D_phy, only: debug_3D,flot,ibase,ghf,ghf0,secyear 
     684    use module3D_phy, only: debug_3D,flot,ibase,ghf,secyear 
    685685     
    686686    implicit none 
    687      
     687 
     688    real,dimension(nx,ny) :: ghf0         !< geothermal heat flux J/m2/a 'o' 
    688689    real,dimension(nx,ny) :: coefdef_maj     !< coefficient deformation 
    689690    real :: increment_ghf 
  • branches/GRISLIv3/SOURCES/taubed-0.3.f90

    r446 r467  
    4444 
    4545  !$USE OMP_LIB  
    46   USE module3D_phy, only: h,bsoc0,bsoc,bdot,sealevel_2d,w0,w1 
     46  USE module3D_phy, only: h,bsoc0,bsoc,bdot,sealevel_2d 
    4747  USE geography, only: nx,ny 
    4848  USE param_phy_mod, only: ro,row,rog,rowg,rom 
     49  USE isostasie_mod, only:w0,w1 
    4950  USE iso_declar,only: nlith,lbloc,charge,dt_iso,tausoc ! module de declaration des variables de l'isostasie 
    5051 
  • branches/GRISLIv3/SOURCES/velocities-polyn-0.3.f90

    r446 r467  
    2626  use runparam, only : itracebug       
    2727  use module3d_phy, only: flotmx,flotmy,ux,uy,sux,suy,sdx,sdy,ubx,uby,& 
    28        hmx,hmy,uxbar,uybar,iglen,cde,divu,uzr,bmelt,bm,flot,front,flgzmx,flgzmy,& 
     28       hmx,hmy,uxbar,uybar,iglen,cde,uzr,bmelt,bm,flot,front,flgzmx,flgzmy,& 
    2929       uzsdot,dtt,uzk,bdot,hdot 
    3030  use geography, only : nx,ny,nz,dx 
     
    3636  real, dimension(nx,ny) :: hdd 
    3737  real, dimension(nx,ny) :: xx 
     38  real, dimension(nx,ny) :: divu         !< divergence de UH 
     39 
    3840 
    3941  if (itracebug.eq.1)  call tracebug(' Entree dans routine SIA_velocity') 
Note: See TracChangeset for help on using the changeset viewer.