diff --git a/src/diagnostics_par_mod.F90 b/src/diagnostics_par_mod.F90
index bb4c0a50880c57f8e480cd40ec6976cd0737cfa7..075bff14fc0611a2b77ec94b1aaa5bd6f5b0fea2 100644
--- a/src/diagnostics_par_mod.F90
+++ b/src/diagnostics_par_mod.F90
@@ -5,10 +5,6 @@ MODULE diagnostics_par
   IMPLICIT NONE
   PRIVATE
 
-
-  LOGICAL, PUBLIC, PROTECTED :: write_theta=.TRUE. 
-  LOGICAL, PUBLIC, PROTECTED :: write_temp=.TRUE.
-  LOGICAL, PUBLIC, PROTECTED :: write_vpar=.TRUE. 
   LOGICAL, PUBLIC, PROTECTED :: write_moments=.TRUE. 
   LOGICAL, PUBLIC, PROTECTED :: write_phi=.TRUE.
   LOGICAL, PUBLIC, PROTECTED :: write_doubleprecision=.FALSE.
@@ -38,8 +34,7 @@ CONTAINS
     IMPLICIT NONE
 
     NAMELIST /OUTPUT_PAR/ nsave_0d , nsave_1d , nsave_2d , nsave_3d
-    NAMELIST /OUTPUT_PAR/ write_theta, write_temp
-    NAMELIST /OUTPUT_PAR/ write_vpar, write_moments, write_phi, write_doubleprecision
+    NAMELIST /OUTPUT_PAR/ write_moments, write_phi, write_doubleprecision
     NAMELIST /OUTPUT_PAR/ resfile0!, rstfile0
 
        READ(lu_in,output_par)
@@ -58,9 +53,6 @@ CONTAINS
     INTEGER, INTENT(in) :: fidres
     CHARACTER(len=256), INTENT(in) :: str
 
-    CALL attach(fidres, TRIM(str), "write_theta", write_theta)
-    CALL attach(fidres, TRIM(str), "write_temp", write_temp)
-    CALL attach(fidres, TRIM(str), "write_vpar", write_vpar)
     CALL attach(fidres, TRIM(str), "write_moments", write_moments)
     CALL attach(fidres, TRIM(str), "write_phi", write_phi)
     CALL attach(fidres, TRIM(str), "write_doubleprecision", write_doubleprecision)
diff --git a/src/fourier_grid_mod.F90 b/src/fourier_grid_mod.F90
index b4d7232070bc12058d8e042ac61d3096767a4f67..abf12e7df69d674b5aa02cbfc0582ceed4e78105 100644
--- a/src/fourier_grid_mod.F90
+++ b/src/fourier_grid_mod.F90
@@ -131,36 +131,37 @@ contains
     CALL attach(fidres, TRIM(str), "kzmax", kzmax)
   END SUBROUTINE fourier_grid_outputinputs
 
-  SUBROUTINE bare(p,j,idx)
+  !============To handle p,j coefficients efficiently
+  FUNCTION bare(p,j) RESULT(idx)
     USE prec_const
     IMPLICIT NONE
     INTEGER, INTENT(in) :: p,j
-    INTEGER, INTENT(out):: idx
+    INTEGER :: idx
 
     idx = (jmaxe + 1)*p + j + 1
 
-  END SUBROUTINE bare
+  END FUNCTION bare
 
-  SUBROUTINE bari(p,j,idx)
+  FUNCTION bari(p,j) RESULT(idx)
     INTEGER, INTENT(in) :: p,j
-    INTEGER, INTENT(out):: idx
+    INTEGER :: idx
 
-    idx = (jmaxi + 1)*p + j + 1
+    idx = Nmome + (jmaxi + 1)*p + j + 1
 
-  END SUBROUTINE bari
+  END FUNCTION bari
 
-  SUBROUTINE rabe(idx, p, j)
+  FUNCTION rabe(idx) RESULT(pj)
     INTEGER, INTENT(in) :: idx
-    INTEGER, INTENT(out):: p,j
-    p = FLOOR(real((idx-1) / (jmaxe + 1)))
-    j = idx - p * (jmaxe+1)
-  END SUBROUTINE rabe
-
-  SUBROUTINE rabi(idx, p, j)
-    INTEGER, INTENT(in):: idx
-    INTEGER, INTENT(out) :: p,j
-    p = FLOOR(real((idx-Nmome - 1) / (jmaxi + 1)))
-    j = (idx-Nmome) - p * (jmaxi+1)
-  END SUBROUTINE rabi
+    INTEGER, DIMENSION(2) :: pj
+    pj(1) = int(FLOOR(real(idx-1) / (jmaxe + 1)))
+    pj(2) = idx - 1 - pj(1) * (jmaxe+1)
+  END FUNCTION rabe
+
+  FUNCTION rabi(idx) RESULT(pj)
+    INTEGER, INTENT (in):: idx
+    INTEGER, DIMENSION(2) :: pj
+    pj(1) = FLOOR(real((idx-Nmome - 1) / (jmaxi + 1)))
+    pj(2) = (idx-Nmome) - 1 - pj(1) * (jmaxi+1)
+  END FUNCTION rabi
 
 END MODULE fourier_grid