Skip to content
Snippets Groups Projects
memory.F90 7.91 KiB
SUBROUTINE memory
  ! Allocate arrays (done dynamically otherwise size is unknown)

  USE array
  USE basic
  USE fields
  USE grid
  USE time_integration
  USE model, ONLY: LINEARITY, KIN_E
  USE collision

  USE prec_const
  IMPLICIT NONE

  ! Electrostatic potential
  CALL allocate_array(           phi, ikxs,ikxe, ikys,ikye, izgs,izge)
  CALL allocate_array(        phi_ZF, ikxs,ikxe, izs,ize)
  CALL allocate_array(        phi_EM, ikys,ikye, izs,ize)
  CALL allocate_array(inv_poisson_op, ikxs,ikxe, ikys,ikye, izs,ize)

  !Electrons arrays
  IF(KIN_E) THEN
  CALL allocate_array(             Ne00, ikxs,ikxe, ikys,ikye, izs,ize)
  CALL allocate_array(           dens_e, ikxs,ikxe, ikys,ikye, izs,ize)
  CALL allocate_array(           upar_e, ikxs,ikxe, ikys,ikye, izs,ize)
  CALL allocate_array(           uper_e, ikxs,ikxe, ikys,ikye, izs,ize)
  CALL allocate_array(           Tpar_e, ikxs,ikxe, ikys,ikye, izs,ize)
  CALL allocate_array(           Tper_e, ikxs,ikxe, ikys,ikye, izs,ize)
  CALL allocate_array(           temp_e, ikxs,ikxe, ikys,ikye, izs,ize)
  CALL allocate_array(         Kernel_e,                ijgs_e,ijge_e, ikxs,ikxe, ikys,ikye, izgs,izge,  0,1)
  CALL allocate_array(        moments_e, ipgs_e,ipge_e, ijgs_e,ijge_e, ikxs,ikxe, ikys,ikye, izgs,izge, 1,ntimelevel )
  CALL allocate_array(    moments_rhs_e,  ips_e,ipe_e,   ijs_e,ije_e,  ikxs,ikxe, ikys,ikye,  izs,ize,  1,ntimelevel )
  CALL allocate_array( nadiab_moments_e, ipgs_e,ipge_e, ijgs_e,ijge_e, ikxs,ikxe, ikys,ikye, izgs,izge)
  CALL allocate_array(     moments_e_ZF, ipgs_e,ipge_e, ijgs_e,ijge_e, ikxs,ikxe, izs,ize)
  CALL allocate_array(     moments_e_EM, ipgs_e,ipge_e, ijgs_e,ijge_e, ikys,ikye, izs,ize)
  CALL allocate_array(          TColl_e,  ips_e,ipe_e,   ijs_e,ije_e , ikxs,ikxe, ikys,ikye, izs,ize)
  CALL allocate_array(             Sepj,  ips_e,ipe_e,   ijs_e,ije_e,  ikxs,ikxe, ikys,ikye, izs,ize)
  CALL allocate_array(           xnepj,   ips_e,ipe_e,   ijs_e,ije_e)
  CALL allocate_array(           xnepp2j, ips_e,ipe_e)
  CALL allocate_array(           xnepp1j, ips_e,ipe_e)
  CALL allocate_array(           xnepm1j, ips_e,ipe_e)
  CALL allocate_array(           xnepm2j, ips_e,ipe_e)
  CALL allocate_array(           xnepjp1,                ijs_e,ije_e)
  CALL allocate_array(           xnepjm1,                ijs_e,ije_e)
  CALL allocate_array(           ynepp1j, ips_e,ipe_e,   ijs_e,ije_e)
  CALL allocate_array(           ynepm1j, ips_e,ipe_e,   ijs_e,ije_e)
  CALL allocate_array(         ynepp1jm1, ips_e,ipe_e,   ijs_e,ije_e)
  CALL allocate_array(         ynepm1jm1, ips_e,ipe_e,   ijs_e,ije_e)
  CALL allocate_array(           zNepm1j, ips_e,ipe_e,   ijs_e,ije_e)
  CALL allocate_array(         zNepm1jp1, ips_e,ipe_e,   ijs_e,ije_e)
  CALL allocate_array(         zNepm1jm1, ips_e,ipe_e,   ijs_e,ije_e)
  ENDIF

  !Ions arrays
  CALL allocate_array(             Ni00, ikxs,ikxe, ikys,ikye, izs,ize)
  CALL allocate_array(           dens_i, ikxs,ikxe, ikys,ikye, izs,ize)
  CALL allocate_array(           upar_i, ikxs,ikxe, ikys,ikye, izs,ize)
  CALL allocate_array(           uper_i, ikxs,ikxe, ikys,ikye, izs,ize)
  CALL allocate_array(           Tpar_i, ikxs,ikxe, ikys,ikye, izs,ize)
  CALL allocate_array(           Tper_i, ikxs,ikxe, ikys,ikye, izs,ize)
  CALL allocate_array(           temp_i, ikxs,ikxe, ikys,ikye, izs,ize)
  CALL allocate_array(         Kernel_i,                ijgs_i,ijge_i, ikxs,ikxe, ikys,ikye, izgs,izge,  0,1)
  CALL allocate_array(        moments_i, ipgs_i,ipge_i, ijgs_i,ijge_i, ikxs,ikxe, ikys,ikye, izgs,izge, 1,ntimelevel )
  CALL allocate_array(    moments_rhs_i,  ips_i,ipe_i,   ijs_i,ije_i,  ikxs,ikxe, ikys,ikye,  izs,ize,  1,ntimelevel )
  CALL allocate_array( nadiab_moments_i, ipgs_i,ipge_i, ijgs_i,ijge_i, ikxs,ikxe, ikys,ikye, izgs,izge)
  CALL allocate_array(     moments_i_ZF, ipgs_i,ipge_i, ijgs_i,ijge_i, ikxs,ikxe, izs,ize)
  CALL allocate_array(     moments_i_EM, ipgs_i,ipge_i, ijgs_i,ijge_i, ikys,ikye, izs,ize)
  CALL allocate_array(          TColl_i,  ips_i,ipe_i,   ijs_i,ije_i,  ikxs,ikxe, ikys,ikye, izs,ize)
  CALL allocate_array(             Sipj,  ips_i,ipe_i,   ijs_i,ije_i,  ikxs,ikxe, ikys,ikye, izs,ize)
  CALL allocate_array( xnipj,   ips_i,ipe_i, ijs_i,ije_i)
  CALL allocate_array( xnipp2j, ips_i,ipe_i)
  CALL allocate_array( xnipp1j, ips_i,ipe_i)
  CALL allocate_array( xnipm1j, ips_i,ipe_i)
  CALL allocate_array( xnipm2j, ips_i,ipe_i)
  CALL allocate_array( xnipjp1, ijs_i,ije_i)
  CALL allocate_array( xnipjm1, ijs_i,ije_i)
  CALL allocate_array(   ynipp1j, ips_i,ipe_i, ijs_i,ije_i)
  CALL allocate_array(   ynipm1j, ips_i,ipe_i, ijs_i,ije_i)
  CALL allocate_array( ynipp1jm1, ips_i,ipe_i, ijs_i,ije_i)
  CALL allocate_array( ynipm1jm1, ips_i,ipe_i, ijs_i,ije_i)
  CALL allocate_array(   zNipm1j, ips_i,ipe_i, ijs_i,ije_i)
  CALL allocate_array( zNipm1jp1, ips_i,ipe_i, ijs_i,ije_i)
  CALL allocate_array( zNipm1jm1, ips_i,ipe_i, ijs_i,ije_i)

  ! Non linear terms and dnjs table
  CALL allocate_array( dnjs, 1,maxj+1, 1,maxj+1, 1,maxj+1)

  ! elect. pot. linear terms
  IF (KIN_E) THEN
    CALL allocate_array( xphij_e,   ips_e,ipe_e, ijs_e,ije_e)
    CALL allocate_array( xphijp1_e, ips_e,ipe_e, ijs_e,ije_e)
    CALL allocate_array( xphijm1_e, ips_e,ipe_e, ijs_e,ije_e)
  ENDIF
  CALL allocate_array( xphij_i,   ips_i,ipe_i, ijs_i,ije_i)
  CALL allocate_array( xphijp1_i, ips_i,ipe_i, ijs_i,ije_i)
  CALL allocate_array( xphijm1_i, ips_i,ipe_i, ijs_i,ije_i)

  ! Curvature and geometry
  CALL allocate_array( Ckxky,   ikxs,ikxe, ikys,ikye,izgs,izge,0,1)
  CALL allocate_array( kparray, ikxs,ikxe, ikys,ikye,izgs,izge,0,1)
  CALL allocate_array(   Jacobian,izgs,izge, 0,1)
  CALL allocate_array(        gxx,izgs,izge, 0,1)
  CALL allocate_array(        gxy,izgs,izge, 0,1)
  CALL allocate_array(        gxz,izgs,izge, 0,1)
  CALL allocate_array(        gyy,izgs,izge, 0,1)
  CALL allocate_array(        gyz,izgs,izge, 0,1)
  CALL allocate_array(        gzz,izgs,izge, 0,1)
  CALL allocate_array(     gradxB,izgs,izge, 0,1)
  CALL allocate_array(     gradyB,izgs,izge, 0,1)
  CALL allocate_array(     gradzB,izgs,izge, 0,1)
  CALL allocate_array(       hatB,izgs,izge, 0,1)
  CALL allocate_array(       hatR,izgs,izge, 0,1)
  CALL allocate_array(       hatZ,izgs,izge, 0,1)
  CALL allocate_array(         Rc,izgs,izge, 0,1)
  CALL allocate_array(       phic,izgs,izge, 0,1)
  CALL allocate_array(         Zc,izgs,izge, 0,1)
  CALL allocate_array(       dxdR,izgs,izge, 0,1)
  CALL allocate_array(       dxdZ,izgs,izge, 0,1)
  call allocate_array(gradz_coeff,izgs,izge, 0,1)

  !___________________ 2x5D ARRAYS __________________________
  !! Collision matrices
  IF (gyrokin_CO) THEN !GK collision matrices (one for each kperp)
    IF (KIN_E) THEN
    CALL allocate_array(  Ceepj, 1,(pmaxe+1)*(jmaxe+1), 1,(pmaxe+1)*(jmaxe+1), ikxs,ikxe, ikys,ikye, izs,ize)
    CALL allocate_array( CeipjT, 1,(pmaxe+1)*(jmaxe+1), 1,(pmaxe+1)*(jmaxe+1), ikxs,ikxe, ikys,ikye, izs,ize)
    CALL allocate_array( CeipjF, 1,(pmaxe+1)*(jmaxe+1), 1,(pmaxi+1)*(jmaxi+1), ikxs,ikxe, ikys,ikye, izs,ize)
    CALL allocate_array( CiepjT, 1,(pmaxi+1)*(jmaxi+1), 1,(pmaxi+1)*(jmaxi+1), ikxs,ikxe, ikys,ikye, izs,ize)
    CALL allocate_array( CiepjF, 1,(pmaxi+1)*(jmaxi+1), 1,(pmaxe+1)*(jmaxe+1), ikxs,ikxe, ikys,ikye, izs,ize)
    ENDIF
    CALL allocate_array(  Ciipj, 1,(pmaxi+1)*(jmaxi+1), 1,(pmaxi+1)*(jmaxi+1), ikxs,ikxe, ikys,ikye, izs,ize)
  ELSE !DK collision matrix (same for every k)
      IF (KIN_E) THEN
      CALL allocate_array(  Ceepj, 1,(pmaxe+1)*(jmaxe+1), 1,(pmaxe+1)*(jmaxe+1), 1,1, 1,1, 1,1)
      CALL allocate_array( CeipjT, 1,(pmaxe+1)*(jmaxe+1), 1,(pmaxe+1)*(jmaxe+1), 1,1, 1,1, 1,1)
      CALL allocate_array( CeipjF, 1,(pmaxe+1)*(jmaxe+1), 1,(pmaxi+1)*(jmaxi+1), 1,1, 1,1, 1,1)
      CALL allocate_array( CiepjT, 1,(pmaxi+1)*(jmaxi+1), 1,(pmaxi+1)*(jmaxi+1), 1,1, 1,1, 1,1)
      CALL allocate_array( CiepjF, 1,(pmaxi+1)*(jmaxi+1), 1,(pmaxe+1)*(jmaxe+1), 1,1, 1,1, 1,1)
      ENDIF
      CALL allocate_array(  Ciipj, 1,(pmaxi+1)*(jmaxi+1), 1,(pmaxi+1)*(jmaxi+1), 1,1, 1,1, 1,1)
 ENDIF
END SUBROUTINE memory