diff --git a/src/MNH/aircraft_balloon_evol.f90 b/src/MNH/aircraft_balloon_evol.f90
index e0d7e555bd4a4de76e3736cee452d6ccfc04e189..d59b33721819904ac9baabd7719c0572b91a2433 100644
--- a/src/MNH/aircraft_balloon_evol.f90
+++ b/src/MNH/aircraft_balloon_evol.f90
@@ -849,7 +849,6 @@ REAL                           :: ZV_BAL   ! horizontal wind speed at balloon lo
 REAL, DIMENSION(SIZE(PZ,3))    :: ZZ       ! altitude of model levels at station location
 REAL, DIMENSION(SIZE(PR,1),SIZE(PR,2),SIZE(PR,3))    :: ZR
 
-
 TPFLYER%NMODELHIST(ISTORE) = TPFLYER%NMODEL
 
 TPFLYER%XX(ISTORE) = TPFLYER%XX_CUR
@@ -889,6 +888,8 @@ END DO
 
 TPFLYER%XFFZ  (:,ISTORE) = TPFLYER%INTERP_HOR_FROM_MASSPOINT( SQRT(PU**2+PV**2) )
 
+TPFLYER%XRHOD (:,ISTORE) = TPFLYER%INTERP_HOR_FROM_MASSPOINT( PRHODREF )
+
 IF (CCLOUD=="LIMA") THEN
   TPFLYER%XCIZ  (:,ISTORE) = TPFLYER%INTERP_HOR_FROM_MASSPOINT( PSV(:,:,:,NSV_LIMA_NI) )
   TPFLYER%XCCZ  (:,ISTORE) = TPFLYER%INTERP_HOR_FROM_MASSPOINT( PSV(:,:,:,NSV_LIMA_NC) )
@@ -906,6 +907,10 @@ CALL Sensor_rare_compute( TPFLYER, ISTORE, PR, PSV, PRHODREF, PCIT, ZTH_EXN, ZZ,
 
 ! vertical wind
 TPFLYER%XWZ  (:,ISTORE) = TPFLYER%INTERP_HOR_FROM_MASSPOINT( ZWM(:,:,:) )
+
+! Dry air density at flyer position
+TPFLYER%XRHOD_SENSOR(ISTORE) = TPFLYER%INTERP_FROM_MASSPOINT( PRHODREF )
+
 IF (SIZE(PTKE)>0) TPFLYER%XTKE  (1,ISTORE) = TPFLYER%INTERP_FROM_MASSPOINT( PTKE )
 IF ( CRAD /= 'NONE' ) TPFLYER%XTSRAD(ISTORE) = TPFLYER%INTERP_HOR_FROM_MASSPOINT(PTS )
 TPFLYER%XTKE_DISS(ISTORE) = TPFLYER%INTERP_FROM_MASSPOINT( XCURRENT_TKE_DISS )
diff --git a/src/MNH/eol_alm.f90 b/src/MNH/eol_alm.f90
index cb82091fdb749ef81faa44a38a7d099384be75f6..648ae6575115848cd28188bfd0ff58c70f1f0855 100644
--- a/src/MNH/eol_alm.f90
+++ b/src/MNH/eol_alm.f90
@@ -382,8 +382,8 @@ DO KTSUBCOUNT=1,INBSUBCOUNT
 !
           IF (LTIPLOSSG) THEN
            ZPHI   = + ZAOA                                      &
-                    + TFARM%XBLA_PITCH(JROT)                    &
-                    + XTWIST_ELT(JROT,JBLA,JBELT)
+                    - TFARM%XBLA_PITCH(JROT)                    &
+                    - XTWIST_ELT(JROT,JBLA,JBELT)
            IF (ZPHI > 0.0) THEN
             ZFTIPL   = (2.0/XPI)*ACOS(MIN(                       &
                         1.0, EXP(-(TTURBINE%NNB_BLADES/2.0)      &
diff --git a/src/MNH/ini_aircraft.f90 b/src/MNH/ini_aircraft.f90
index 90beb1354dca150ada71e2b156dfdd2a2907ef1d..40be297467af3fdff58183479da32c89a667975a 100644
--- a/src/MNH/ini_aircraft.f90
+++ b/src/MNH/ini_aircraft.f90
@@ -18,74 +18,6 @@ CONTAINS
 !     #######################
       SUBROUTINE INI_AIRCRAFT
 !     #######################
-!
-!
-!!****  *INI_AIRCRAFT* - user initializes the aircraft flight path
-!!
-!!    PURPOSE
-!!    -------
-!
-!
-!!**  METHOD
-!!    ------
-!!    
-!!   Must be defined (for each aircraft):
-!!   ---------------
-!!
-!!  No default exist for these variables.
-!!  ************************************
-!!
-!!  1) the model in which the aircraft will evolve
-!!     if NOT initialized, the aircraft is NOT used.
-!!
-!!  2) the possibility to switch from a model to its dad or kid
-!!       'FIX' : NMODEL used during the run
-!!       'MOB' : best resolution model used. NMODEL=1 is used at the beginning
-!!
-!!
-!!  3) the type of aircraft
-!!
-!!     'AIRCRAFT' for aircraft
-!!
-!!  4) the takeoff date and time
-!!
-!!  5) the number of flight path segments (SEG)
-!!
-!!  6) the (SEG  ) duration of flight in the segments, in the flight order (sec.)
-!!
-!!  6bis) TAIRCRAFT%LALTDEF : flag to define the mode of initialisation of
-!!        aircraft altitude TRUE for pressure (corresponding to %XSEGP)
-!!        or FALSE for Z (corresponding to %XSEGZ)
-!!
-!!  7) the (SEG+1) latitudes of the segments ends, in the flight order
-!!     first point is take-off
-!!     last  point is landing
-!!
-!!  8) the (SEG+1) longitudes of the segments ends, in the flight order
-!!
-!!  9) the (SEG+1) pressure (%XSEGP) or Z (%XSEGZ) of the segments ends, in the flight order
-!!
-!!
-!!
-!!   Can be defined  (for each aircraft):
-!!   --------------
-!!
-!!
-!!  9) the time step for data storage.
-!!    default is 60s
-!!
-!! 10) the name or title describing the aircraft (8 characters)
-!!     default is the aircraft type (6 characters) + the aircraft numbers (2 characters)
-!!
-!!
-!!    EXTERNAL
-!!    --------
-!!
-!!    IMPLICIT ARGUMENTS
-!!    ------------------
-!!
-!!    REFERENCE
-!!    ---------
 !!
 !!    AUTHOR
 !!    ------
diff --git a/src/MNH/ini_balloon.f90 b/src/MNH/ini_balloon.f90
index 3b60fd7e5509ca79ac61429a68a738c1f1fb99a1..bbcaa9abad8b08aa5af220fc8fc9cc6055de02b5 100644
--- a/src/MNH/ini_balloon.f90
+++ b/src/MNH/ini_balloon.f90
@@ -17,84 +17,6 @@ CONTAINS
       SUBROUTINE INI_BALLOON
 !     ######################
 !
-!
-!!****  *INI_BALLOON* - user initializes the balloon characteristics
-!!
-!!    PURPOSE
-!!    -------
-!
-!
-!!**  METHOD
-!!    ------
-!!    
-!!    For constant volume Balloon, horizontal advection using horizontal wind
-!!        vertical speed of the balloon calculated using the balloon equation
-!!        (Koffi et AL 2000, JAS vol 57 P.2007-2021)
-!!
-!!   Must be defined (for each balloon):
-!!   ---------------
-!!
-!!  No default exist for these variables.
-!!  ************************************
-!!
-!!  1) the model in which the balloon will evolve
-!!     if NOT initialized, the balloon is NOT used.
-!!  1.1) the possibility to switch from a model to its dad or kid
-!!       'FIX' : NMODEL used during the run
-!!       'MOB' : best resolution model used. NMODEL=1 is used at the beginning
-!!
-!!  2) the type of balloon
-!!
-!!     'RADIOS' for radiosounding balloon
-!!     'ISODEN' for iso-density balloon
-!!     'CVBALL' for constant volume Balloon
-!!
-!!  3) the launching date and time
-!!
-!!  4) the latitude of the launching site
-!!
-!!  5) the longitude of the launching site
-!!
-!!  6) the altitude of the launching site (for 'RADIOS')
-!!
-!!                      OR
-!!
-!!     the altitude OR pressure of balloon at start of the leveled flight
-!!     (for 'ISODEN'). In this case, the density of this level will be computed,
-!!     and the balloon will evolve at this density level.
-!!
-!!
-!!
-!!   Can be defined  (for each balloon):
-!!   --------------
-!!
-!!  7) the ascentional vertical speed of the ballon (in calm air) (for 'RADIOS')
-!!     default is 5m/s
-!!
-!!  8) the time step for data storage.
-!!    default is 60s
-!!
-!!  9) the name or title describing the balloon (8 characters)
-!!     default is the balloon type (6 characters) + the balloon numbers (2 characters)
-!!
-!!  10) for 'CVBALL' the aerodynamic drag coefficient of the balloon
-!!
-!!  11) for 'CVBALL' the induced drag coefficient (i.e. air shifted by the balloon)
-!!
-!!  12) for 'CVBALL' the volume of the balloon
-!!
-!!  13) for 'CVBALL' the mass of the balloon
-!!
-!!
-!!    EXTERNAL
-!!    --------
-!!
-!!    IMPLICIT ARGUMENTS
-!!    ------------------
-!!
-!!    REFERENCE
-!!    ---------
-!!
 !!    AUTHOR
 !!    ------
 !!      Valery Masson             * Meteo-France *
diff --git a/src/MNH/modd_sensor.f90 b/src/MNH/modd_sensor.f90
index 8d951d4a6aff09b228ebbfdbdac34332fd9ea89e..18ca64c27d6941aaa3a87a398614b0900f1867ae 100644
--- a/src/MNH/modd_sensor.f90
+++ b/src/MNH/modd_sensor.f90
@@ -101,7 +101,9 @@ MODULE MODD_SENSOR
       REAL, DIMENSION(:,:,:), ALLOCATABLE :: XR      ! r*(n)
       REAL, DIMENSION(:,:,:), ALLOCATABLE :: XSV     ! Sv*(n)
       REAL, DIMENSION(:),     ALLOCATABLE :: XTSRAD  ! surface temperature Ts(n)
+      REAL, DIMENSION(:),     ALLOCATABLE :: XRHOD_SENSOR ! density of dry air at sensor position
 
+      REAL, DIMENSION(:,:),   ALLOCATABLE :: XRHOD      ! density of dry air
       REAL, DIMENSION(:,:),   ALLOCATABLE :: XCIZ       ! Ice concentration
       REAL, DIMENSION(:,:),   ALLOCATABLE :: XCCZ       ! Cloud concentration (LIMA)
       REAL, DIMENSION(:,:),   ALLOCATABLE :: XCRZ       ! Rain concentration (LIMA)
@@ -214,8 +216,11 @@ MODULE MODD_SENSOR
       ELSE
         ALLOCATE( TPSENSOR%XTSRAD(0) )
       END IF
+      ALLOCATE( TPSENSOR%XRHOD_SENSOR(KSTORE) ) ; IVARSIZE = IVARSIZE + 1
 
       IF ( OVERTPROF ) THEN
+        ALLOCATE( TPSENSOR%XRHOD(IKU, KSTORE) )      ; IVARSIZE = IVARSIZE + IKU
+
         IF ( CCLOUD == 'LIMA') THEN
           ALLOCATE( TPSENSOR%XCIZ    (IKU, KSTORE) ) ; IVARSIZE = IVARSIZE + IKU
           ALLOCATE( TPSENSOR%XCCZ    (IKU, KSTORE) ) ; IVARSIZE = IVARSIZE + IKU
@@ -235,6 +240,7 @@ MODULE MODD_SENSOR
         ALLOCATE( TPSENSOR%XCRARE    (IKU, KSTORE) ) ; IVARSIZE = IVARSIZE + IKU
         ALLOCATE( TPSENSOR%XCRARE_ATT(IKU, KSTORE) ) ; IVARSIZE = IVARSIZE + IKU
       ELSE
+        ALLOCATE( TPSENSOR%XRHOD   (0, 0) )
         ALLOCATE( TPSENSOR%XCIZ    (0, 0) )
         ALLOCATE( TPSENSOR%XCCZ    (0, 0) )
         ALLOCATE( TPSENSOR%XCRZ    (0, 0) )
@@ -255,6 +261,8 @@ MODULE MODD_SENSOR
       TPSENSOR%XR        (:,:,:) = XUNDEF
       TPSENSOR%XSV       (:,:,:) = XUNDEF
       TPSENSOR%XTSRAD    (:)     = XUNDEF_SFX
+      TPSENSOR%XRHOD_SENSOR(:)   = XNEGUNDEF
+      TPSENSOR%XRHOD     (:,:)   = XNEGUNDEF
       TPSENSOR%XCIZ      (:,:)   = XUNDEF
       TPSENSOR%XCCZ      (:,:)   = XUNDEF
       TPSENSOR%XCRZ      (:,:)   = XUNDEF
@@ -288,6 +296,8 @@ MODULE MODD_SENSOR
       DEALLOCATE( TPSENSOR%XR         )
       DEALLOCATE( TPSENSOR%XSV        )
       DEALLOCATE( TPSENSOR%XTSRAD     )
+      DEALLOCATE( TPSENSOR%XRHOD_SENSOR )
+      DEALLOCATE( TPSENSOR%XRHOD      )
       DEALLOCATE( TPSENSOR%XCIZ       )
       DEALLOCATE( TPSENSOR%XCCZ       )
       DEALLOCATE( TPSENSOR%XCRZ       )
@@ -1002,8 +1012,10 @@ MODULE MODD_SENSOR
       IF ( CRAD /= 'NONE' ) THEN
         PBUFFER(KPOS:KPOS+ISTORES-1) = TPSENSOR%XTSRAD(1:ISTORES) ; KPOS = KPOS + ISTORES
       END IF
+      PBUFFER(KPOS:KPOS+ISTORES-1) = TPSENSOR%XRHOD_SENSOR(1:ISTORES) ; KPOS = KPOS + ISTORES
 
-      IF ( SIZE( TPSENSOR%XIWCZ ) > 0 ) THEN
+      IF ( SIZE( TPSENSOR%XRHOD ) > 0 ) THEN
+        PBUFFER(KPOS:KPOS+IKU*ISTORES-1) = RESHAPE( TPSENSOR%XRHOD     (:,1:ISTORES), [IKU*ISTORES] ) ; KPOS = KPOS + IKU * ISTORES
         IF ( CCLOUD(1:3) == 'ICE') THEN
           PBUFFER(KPOS:KPOS+IKU*ISTORES-1) = RESHAPE( TPSENSOR%XCIZ    (:,1:ISTORES), [IKU*ISTORES] ) ; KPOS = KPOS + IKU * ISTORES
         END IF
@@ -1127,8 +1139,10 @@ MODULE MODD_SENSOR
       IF ( CRAD /= 'NONE' ) THEN
         TPSENSOR%XTSRAD(1:KSTORE) = PBUFFER(KPOS:KPOS+KSTORE-1) ; KPOS = KPOS + KSTORE
       END IF
+      TPSENSOR%XRHOD_SENSOR(1:KSTORE) = PBUFFER(KPOS:KPOS+KSTORE-1) ; KPOS = KPOS + KSTORE
 
-      IF ( SIZE( TPSENSOR%XIWCZ ) > 0 ) THEN
+      IF ( SIZE( TPSENSOR%XRHOD ) > 0 ) THEN
+        TPSENSOR%XRHOD     (:,1:KSTORE) = RESHAPE( PBUFFER(KPOS:KPOS+IKU*KSTORE-1), [ IKU, KSTORE ] ) ; KPOS = KPOS + IKU * KSTORE
         IF ( CCLOUD(1:3) == 'ICE' ) THEN
           TPSENSOR%XCIZ    (:,1:KSTORE) = RESHAPE( PBUFFER(KPOS:KPOS+IKU*KSTORE-1), [ IKU, KSTORE ] ) ; KPOS = KPOS + IKU * KSTORE
         END IF
diff --git a/src/MNH/modd_type_statprof.f90 b/src/MNH/modd_type_statprof.f90
index 933235718d0480315b9ac08e85536388238b0e45..0e7b81bb08c323592b33882e5df07a13315d8072 100644
--- a/src/MNH/modd_type_statprof.f90
+++ b/src/MNH/modd_type_statprof.f90
@@ -110,7 +110,6 @@ TYPE, EXTENDS( TSTATPROFDATA ) ::  TPROFILERDATA
   REAL, DIMENSION(:,:),   ALLOCATABLE :: XTHV       ! thv(n)
   REAL, DIMENSION(:,:),   ALLOCATABLE :: XVISIGUL   ! VISI GULTEPE(n)
   REAL, DIMENSION(:,:),   ALLOCATABLE :: XVISIKUN   ! VISI KUNKEL(n)
-  REAL, DIMENSION(:,:),   ALLOCATABLE :: XRHOD      ! density of dry air/moist air
   REAL, DIMENSION(:,:,:), ALLOCATABLE :: XAER       ! AER*(n) aerosol extinction
 
   REAL, DIMENSION(:), ALLOCATABLE :: XIWV ! integrated water vpour(n)
@@ -322,7 +321,6 @@ SUBROUTINE DATA_ARRAYS_ALLOCATE_PROFILER( TPSENSOR, KSTORE )
     ELSE
       ALLOCATE( TPSENSOR%XVISIKUN  (0, 0) )
     END IF
-    ALLOCATE( TPSENSOR%XRHOD     (IKU, KSTORE) )        ; IVARSIZE = IVARSIZE + IKU
     ALLOCATE( TPSENSOR%XAER      (IKU, KSTORE, NAER ) ) ; IVARSIZE = IVARSIZE + IKU * NAER
 
     ALLOCATE( TPSENSOR%XIWV(KSTORE) ) ; IVARSIZE = IVARSIZE + 1
@@ -341,7 +339,6 @@ SUBROUTINE DATA_ARRAYS_ALLOCATE_PROFILER( TPSENSOR, KSTORE )
     TPSENSOR%XTHV      (:,:) = XUNDEF
     IF ( CCLOUD == 'C2R2' .OR. CCLOUD == 'KHKO' )  TPSENSOR%XVISIGUL(:,:) = XUNDEF
     IF ( CCLOUD /= 'NONE' .AND. CCLOUD /= 'REVE' ) TPSENSOR%XVISIKUN(:,:) = XUNDEF
-    TPSENSOR%XRHOD     (:,:) = XUNDEF
     TPSENSOR%XAER      (:,:,:) = XUNDEF
 
     TPSENSOR%XIWV(:) = XUNDEF
@@ -370,7 +367,6 @@ SUBROUTINE DATA_ARRAYS_ALLOCATE_PROFILER( TPSENSOR, KSTORE )
     DEALLOCATE( TPSENSOR%XTHV       )
     DEALLOCATE( TPSENSOR%XVISIGUL   )
     DEALLOCATE( TPSENSOR%XVISIKUN   )
-    DEALLOCATE( TPSENSOR%XRHOD      )
     DEALLOCATE( TPSENSOR%XAER       )
 
     DEALLOCATE( TPSENSOR%XIWV )
@@ -524,7 +520,6 @@ SUBROUTINE DATA_ARRAYS_ALLOCATE_PROFILER( TPSENSOR, KSTORE )
     IF ( CCLOUD /= 'NONE' .AND. CCLOUD /= 'REVE' ) THEN
       PBUFFER(KPOS:KPOS+IKU*ISTORES-1) = RESHAPE( TPSENSOR%XVISIKUN(:,1:ISTORES), [IKU*ISTORES] ) ; KPOS = KPOS + IKU * ISTORES
     END IF
-    PBUFFER(KPOS:KPOS+IKU*ISTORES-1) = RESHAPE( TPSENSOR%XRHOD(:,1:ISTORES), [IKU*ISTORES] ) ; KPOS = KPOS + IKU * ISTORES
     PBUFFER(KPOS:KPOS+IKU*ISTORES*NAER-1) = RESHAPE( TPSENSOR%XAER(:,1:ISTORES,:), [IKU*ISTORES*NAER] )
     KPOS = KPOS + IKU * ISTORES * NAER
 
@@ -650,7 +645,6 @@ SUBROUTINE DATA_ARRAYS_ALLOCATE_PROFILER( TPSENSOR, KSTORE )
     IF ( CCLOUD /= 'NONE' .AND. CCLOUD /= 'REVE' ) THEN
       TPSENSOR%XVISIKUN(:,1:KSTORE) = RESHAPE( PBUFFER(KPOS:KPOS+IKU*KSTORE-1), [ IKU, KSTORE ] ) ; KPOS = KPOS + IKU * KSTORE
     END IF
-    TPSENSOR%XRHOD(:,1:KSTORE) = RESHAPE( PBUFFER(KPOS:KPOS+IKU*KSTORE-1), [ IKU, KSTORE ] ) ; KPOS = KPOS + IKU * KSTORE
     TPSENSOR%XAER(:,1:KSTORE,:) = RESHAPE( PBUFFER(KPOS:KPOS+IKU*KSTORE*NAER-1), [ IKU, KSTORE, NAER ] )
     KPOS = KPOS + IKU * KSTORE * NAER
 
diff --git a/src/MNH/modeln.f90 b/src/MNH/modeln.f90
index 387f6c4ecdd9bfcdf09b4479ca4a56663786628d..16356ea6421a4f5e1ed985bca3a6cb7382569cb6 100644
--- a/src/MNH/modeln.f90
+++ b/src/MNH/modeln.f90
@@ -2190,7 +2190,7 @@ END IF
 !               --------------------------------
 !
 IF ( LSTATION ) &
-  CALL STATION_n( XZZ, XUT, XVT, XWT, XTHT, XRT, XSVT, XTKET, XTSRAD, XPABST )
+  CALL STATION_n( XZZ, XRHODREF, XUT, XVT, XWT, XTHT, XRT, XSVT, XTKET, XTSRAD, XPABST )
 !
 !---------------------------------------------------------
 !
diff --git a/src/MNH/profilern.f90 b/src/MNH/profilern.f90
index f36998381ae2833a9ae0d0969b8245b96dcb324f..f95533090650d9f5c3252f178feb93068d322e3a 100644
--- a/src/MNH/profilern.f90
+++ b/src/MNH/profilern.f90
@@ -212,6 +212,8 @@ IF ( .NOT. TPROFILERS_TIME%STORESTEP_CHECK_AND_SET( IN ) ) RETURN !No profiler s
 !*      8.   DATA RECORDING
 !            --------------
 !
+IF ( NUMBPROFILER_LOC == 0 ) RETURN ! No profiler on this process
+
 ZTEMP(:,:,:)=PTH(:,:,:)*(PP(:,:,:)/ XP00) **(XRD/XCPD)
 ! Theta_v
 ZTHV(:,:,:) = PTH(:,:,:) / (1.+WATER_SUM(PR(:,:,:,:)))*(1.+PR(:,:,:,1)/ZRDSRV)
@@ -366,6 +368,12 @@ PROFILER: DO JP = 1, NUMBPROFILER_LOC
     TPROFILERS(JP)%XAER(:,IN,JSV) = TPROFILERS(JP)%INTERP_HOR_FROM_MASSPOINT( ZWORK2(:,:,:,JSV) )
   END DO
   IF (SIZE(PTKE)>0) TPROFILERS(JP)%XTKE  (:,IN) = TPROFILERS(JP)%INTERP_HOR_FROM_MASSPOINT( PTKE )
+
+  ! XRHOD_SENSOR is not computed for profilers because not very useful
+  ! If needed, the interpolation must also be done vertically
+  ! (and therefore the vertical interpolation coefficients have to be computed)
+  ! TPROFILERS(JP)%XRHOD_SENSOR(IN) = ...
+
   IF ( CRAD /= 'NONE' ) TPROFILERS(JP)%XTSRAD(IN) = TPROFILERS(JP)%INTERP_HOR_FROM_MASSPOINT( PTS )
   !
   IF ( LDIAG_SURFRAD_PROF ) CALL STATPROF_DIAG_SURFRAD(TPROFILERS(JP), IN )
diff --git a/src/MNH/stationn.f90 b/src/MNH/stationn.f90
index 793d92093ce1ba2c441e4afb34b6223b400c5a1d..6ef64ccf5162ce40563307b5f51ed8cf50e71303 100644
--- a/src/MNH/stationn.f90
+++ b/src/MNH/stationn.f90
@@ -9,11 +9,12 @@ MODULE MODI_STATION_n
 !
 INTERFACE
 !
-      SUBROUTINE STATION_n( PZ,                             &
+      SUBROUTINE STATION_n( PZ, PRHODREF,                   &
                             PU, PV, PW, PTH, PR, PSV, PTKE, &
                             PTS, PP )
 !
 REAL, DIMENSION(:,:,:),   INTENT(IN)     :: PZ     ! z array
+REAL, DIMENSION(:,:,:),   INTENT(IN)     :: PRHODREF ! dry air density of the reference state
 REAL, DIMENSION(:,:,:),   INTENT(IN)     :: PU     ! horizontal wind X component
 REAL, DIMENSION(:,:,:),   INTENT(IN)     :: PV     ! horizontal wind Y component
 REAL, DIMENSION(:,:,:),   INTENT(IN)     :: PW     ! vertical wind
@@ -33,7 +34,7 @@ END INTERFACE
 END MODULE MODI_STATION_n
 !
 !     #######################################################
-      SUBROUTINE STATION_n( PZ,                             &
+      SUBROUTINE STATION_n( PZ, PRHODREF,                   &
                             PU, PV, PW, PTH, PR, PSV, PTKE, &
                             PTS, PP )
 !     #######################################################
@@ -101,6 +102,7 @@ IMPLICIT NONE
 !
 !
 REAL, DIMENSION(:,:,:),   INTENT(IN)     :: PZ     ! z array
+REAL, DIMENSION(:,:,:),   INTENT(IN)     :: PRHODREF ! dry air density of the reference state
 REAL, DIMENSION(:,:,:),   INTENT(IN)     :: PU     ! horizontal wind X component
 REAL, DIMENSION(:,:,:),   INTENT(IN)     :: PV     ! horizontal wind Y component
 REAL, DIMENSION(:,:,:),   INTENT(IN)     :: PW     ! vertical wind
@@ -165,6 +167,8 @@ STATION: DO JS = 1, NUMBSTAT_LOC
     TSTATIONS(JS)%XSV(1,IN,JSV) = TSTATIONS(JS)%INTERP_HOR_FROM_MASSPOINT( PSV(:,:,JK,JSV) )
   END DO
 
+  TSTATIONS(JS)%XRHOD_SENSOR(IN) = TSTATIONS(JS)%INTERP_HOR_FROM_MASSPOINT( PRHODREF(:,:,JK) )
+
   IF (SIZE(PTKE)>0) TSTATIONS(JS)%XTKE(1,IN) = TSTATIONS(JS)%INTERP_HOR_FROM_MASSPOINT( PTKE(:,:,JK) )
   IF ( CRAD /= 'NONE' ) TSTATIONS(JS)%XTSRAD(IN) = TSTATIONS(JS)%INTERP_HOR_FROM_MASSPOINT( PTS )
   TSTATIONS(JS)%XZS  = TSTATIONS(JS)%INTERP_HOR_FROM_MASSPOINT( PZ(:,:,1+JPVEXT))
diff --git a/src/MNH/write_aircraft_balloon.f90 b/src/MNH/write_aircraft_balloon.f90
index 0678daffcf2abf43cc85ecc6f40e7d99bf116203..61be44dab866a3aeb3082d101aaf1cf9608bebd0 100644
--- a/src/MNH/write_aircraft_balloon.f90
+++ b/src/MNH/write_aircraft_balloon.f90
@@ -205,7 +205,7 @@ USE MODD_SALT,             ONLY: LSALT, NMODE_SLT
 
 use mode_aircraft_balloon, only: Aircraft_balloon_longtype_get
 USE MODE_MODELN_HANDLER,   ONLY: GET_CURRENT_MODEL_INDEX
-use mode_sensor,           only: Add_dust_data, Add_fixpoint, Add_orilam_data, Add_point, Add_profile, Add_salt_data, &
+use mode_sensor,           only: Add_dust_data, Add_orilam_data, Add_point, Add_profile, Add_salt_data, &
                                  Sensor_current_processes_number_get, &
                                  ccomment, ctitle, cunit, xwork6, &
                                  Sensor_write_workarrays_allocate, Sensor_write_workarrays_deallocate
@@ -246,7 +246,7 @@ IF ( IMI /= TPFLYER%NMODEL ) RETURN
 !
 IKU = SIZE(TPFLYER%XRTZ,1) !number of vertical levels
 !
-IPROC = 9 + IRR + SIZE(TPFLYER%XSV,3) + 2 + SIZE(TPFLYER%XSVW_FLUX,2)
+IPROC = 10 + IRR + SIZE(TPFLYER%XSV,3) + 2 + SIZE(TPFLYER%XSVW_FLUX,2)
 IF ( IRR > 1 ) IPROC = IPROC + 1
 IF ( SIZE( TPFLYER%XTKE ) > 0 ) IPROC = IPROC + 1
 IPROC = IPROC + 1 ! TKE_DISS
@@ -318,7 +318,9 @@ IF ( IRR > 1 ) THEN !cloud water is present
   call Add_point( 'LWC', 'cloud liquid water content', 'g m-3', ZLWC(:) )
   DEALLOCATE( ZLWC, ZRHO )
 END IF
-!
+
+call Add_point( 'Rhod', 'Density of dry air', 'kg m-3', tpflyer%xrhod_sensor )
+
 IF (SIZE(TPFLYER%XTKE)>0) call Add_point( 'Tke', 'Turbulent kinetic energy', 'm2 s-2', tpflyer%xtke(1,:) )
 !
 call Add_point( 'H_FLUX',  'sensible flux', 'W m-2', tpflyer%xthw_flux(:) )
@@ -420,7 +422,7 @@ call Sensor_write_workarrays_deallocate( )
 !----------------------------------------------------------------------------
 !Treat vertical profiles
 
-IPROCZ = 8 + IRR
+IPROCZ = 9 + IRR
 IF ( CCLOUD == 'LIMA' )     IPROCZ = IPROCZ + 3
 IF ( CCLOUD(1:3) == 'ICE' ) IPROCZ = IPROCZ + 1
 
@@ -441,6 +443,7 @@ call Add_profile( 'FF', 'Horizontal wind', 'm s-1', tpflyer%xffz(:,:) )
 call Add_profile( 'IWC', 'Ice water content',    'kg m-3', tpflyer%xiwcz(:,:) )
 call Add_profile( 'LWC', 'Liquid water content', 'kg m-3', tpflyer%xlwcz(:,:) )
 
+call Add_profile( 'Rhod', 'Density of dry air',  'kg m-3', tpflyer%xrhod(:,:) )
 IF ( CCLOUD == 'LIMA' ) THEN
   call Add_profile( 'CCLOUDT', 'liquid cloud concentration', 'kg-1', tpflyer%xccz(:,:) )
   call Add_profile( 'CRAINT',  'Rain concentration',         'kg-1', tpflyer%xcrz(:,:) )
diff --git a/src/MNH/write_profilern.f90 b/src/MNH/write_profilern.f90
index 3449ccdec4026d66313470a64b71b0550a5e9b10..a5f1ddd398c231fed6087c15cf4b9da3a372d016 100644
--- a/src/MNH/write_profilern.f90
+++ b/src/MNH/write_profilern.f90
@@ -145,7 +145,7 @@ if ( nrr >= 5 ) call Add_profile( 'Rs', 'Snow mixing ratio',               'kg k
 if ( nrr >= 6 ) call Add_profile( 'Rg', 'Graupel mixing ratio',            'kg kg-1', tpprofiler%xr(:,:,6) )
 if ( nrr >= 7 ) call Add_profile( 'Rh', 'Hail mixing ratio',               'kg kg-1', tpprofiler%xr(:,:,7) )
 
-call Add_profile( 'Rhod', 'Density of dry air in moist', 'kg m-3', tpprofiler%xrhod )
+call Add_profile( 'Rhod', 'Density of dry air', 'kg m-3', tpprofiler%xrhod )
 if ( cturb == 'TKEL') &
   call Add_profile( 'Tke', 'Turbulent kinetic energy', 'm2 s-2', tpprofiler%xtke )
 
@@ -265,6 +265,10 @@ IF( CRAD /= 'NONE' )  IPROC = IPROC + 1 !Tsrad term
 
 call Sensor_write_workarrays_allocate( 1, istore, iproc )
 
+! xrhod_sensor NOT computed => not written
+! if needed, please add its computation in STATION_n
+! call Add_point( 'Rhod', 'Density of dry air', 'kg m-3', tpstation%xrhod_sensor )
+
 if ( ldiag_surfrad_prof ) call Add_diag_surfrad_data( tpprofiler )
 
 call Add_point( 'IWV', 'Integrated Water Vapour',   'kg m-2', tpprofiler%xiwv )
diff --git a/src/MNH/write_stationn.f90 b/src/MNH/write_stationn.f90
index cd1cafb7bfed5b43972d08c7b557bc662cc6b17a..cbdaa5748e648415c397bc3e139ba852b8468fe5 100644
--- a/src/MNH/write_stationn.f90
+++ b/src/MNH/write_stationn.f90
@@ -70,7 +70,7 @@ type(tfieldmetadata_base), dimension(:), allocatable :: tzfields
 !
 !----------------------------------------------------------------------------
 !
-IPROC = 5 + SIZE(TPSTATION%XR,3) + SIZE(TPSTATION%XSV,3)
+IPROC = 6 + SIZE(TPSTATION%XR,3) + SIZE(TPSTATION%XSV,3)
 
 IF ( CTURB == 'TKEL' ) IPROC = IPROC + 1
 IF (LDIAG_SURFRAD_STAT) THEN
@@ -123,6 +123,8 @@ do jrr = 1, SIZE( tpstation%xr, 3 )
   end select
 end do
 
+call Add_point( 'Rhod', 'Density of dry air', 'kg m-3', tpstation%xrhod_sensor )
+
 if ( cturb == 'TKEL' ) call Add_point( 'Tke', 'Turbulent kinetic energy', 'm2 s-2', tpstation%xtke(1,:) )
 
 if ( nsv > 0 ) then
diff --git a/src/Rules.LXcray.mk b/src/Rules.LXcray.mk
index 861de4c1319fc584b227f9d2c428c80f95fffd6f..b1579f030f00360fb1d80bba93a12b5bbcbc5208 100644
--- a/src/Rules.LXcray.mk
+++ b/src/Rules.LXcray.mk
@@ -185,7 +185,7 @@ ifeq ($(shell test $(CFV) -ge 1402 ; echo $$?),0)
 CPPFLAGS_MNH       += -DMNH_COMPILER_CCE_1403
 endif
 CPPFLAGS_MNH       += -DMNH_EXPAND -DMNH_EXPAND_LOOP -DMNH_EXPAND_OPENACC
-CPPFLAGS_MNH       += -imacros MNH_OPENACC_NV_CR.CPP
+#CPPFLAGS_MNH       += -imacros MNH_OPENACC_NV_CR.CPP
 ifdef VER_GA
 CPPFLAGS_SURCOUCHE += -DMNH_GA
 INC                += -I${GA_ROOT}/include
diff --git a/src/configure b/src/configure
index ece7ee154d2c13a57d2c68023691d60964540730..f22c0235f095657803dd5d5892f217ea3e796925 100755
--- a/src/configure
+++ b/src/configure
@@ -54,22 +54,24 @@ case "$TARG" in
 'Linux login'*)
                 export ARCH=${ARCH:-LXcray}
                 export VER_MPI=${VER_MPI:-MPICRAY}
-                export OPTLEVEL=${OPTLEVEL:-OPENACC}
+#                export OPTLEVEL=${OPTLEVEL:-OPENACC}
+                export OPTLEVEL=${OPTLEVEL:-O2}
                 export MVWORK=${MVWORK:-NO}
                 export VER_CDF=${VER_CDF:-CDFAUTO}
 if [ "${VER_MPI}" == "MPICRAY" ] 
 then	
 export MNHENV=${MNHENV:-"
 module purge
-module load craype-x86-trento
+#module load craype-x86-trento
+module load craype-x86-genoa
 module load craype-network-ofi
 module load PrgEnv-cray/8.3.3
-module load cce/15.0.0
+module load cce/15.0.1
 module load craype/2.7.19
-module load cray-mpich/8.1.21
+module load cray-mpich/8.1.24
 module load libfabric/1.15.2.0
-module load craype-accel-amd-gfx90a
-module load rocm/5.2.3
+#module load craype-accel-amd-gfx90a
+module load rocm/5.3.0
 
 export CCE_ALIAS_NONE=:on
 export CCE_NO_PTR_TO_PTR_ALIAS=:on
diff --git a/src/job_make_examples_HPE_adastra_genoa b/src/job_make_examples_HPE_adastra_genoa
new file mode 100755
index 0000000000000000000000000000000000000000..748fac3e0def27fc0474208dd6853444cb3e316c
--- /dev/null
+++ b/src/job_make_examples_HPE_adastra_genoa
@@ -0,0 +1,68 @@
+#!/bin/bash
+#SBATCH -J Examples
+#SBATCH -N 1            # nodes number
+#SBATCH -n 4            # CPUs number (on all nodes) 
+#SBATCH -C GENOA
+##SBATCH --exclusive           
+#SBATCH -o Examples.eo%j   #
+#SBATCH -e Examples.eo%j   #
+#SBATCH -t 01:00:00    # time limit
+#SBATCH --export=NONE
+#SBATCH -A mnh # put here you account/projet name
+
+# Echo of commands
+ulimit -c 0
+ulimit -s unlimited
+# Stop job at first error
+#set -e
+set -x
+# Machine name
+hostname 
+
+unset MAKEFLAGS
+
+. ../conf/profile_mesonh-LXcray-R8I4-MNH-V5-6-1-MPICRAY-O2
+export MONORUN="Exec srun -l -n 1 --export=ALL"
+export MPIRUN="Exec srun -l -n 4 --export=ALL"
+export POSTRUN="echo "
+
+cd $SRC_MESONH/MY_RUN/KTEST/003_KW78 
+make -k
+#
+echo "#################################################################################"
+echo "##NEXT CASE######################################################################"
+echo "#################################################################################"
+cd $SRC_MESONH/MY_RUN/KTEST/001_2Drelief 
+make -k
+#
+echo "#################################################################################"
+echo "##NEXT CASE######################################################################"
+echo "#################################################################################"
+cd $SRC_MESONH/MY_RUN/KTEST/002_3Drelief 
+make -k
+#
+echo "#################################################################################"
+echo "##NEXT CASE######################################################################"
+echo "#################################################################################"
+
+cd $SRC_MESONH/MY_RUN/KTEST/004_Reunion
+make -k << EOF 
+
+
+EOF
+#
+echo "#################################################################################"
+echo "##NEXT CASE######################################################################"
+echo "#################################################################################"
+cd $SRC_MESONH/MY_RUN/KTEST/007_16janvier
+make -k << EOF 
+
+
+EOF
+#
+echo "#################################################################################"
+echo "##NEXT CASE######################################################################"
+echo "#################################################################################"
+cd $SRC_MESONH/MY_RUN/KTEST/014_LIMA 
+make -k
+
diff --git a/src/job_make_mesonh_HPE_adastra_genoa b/src/job_make_mesonh_HPE_adastra_genoa
new file mode 100755
index 0000000000000000000000000000000000000000..c7816c7764735623a0c0ba94cea0fcaef41a39d4
--- /dev/null
+++ b/src/job_make_mesonh_HPE_adastra_genoa
@@ -0,0 +1,22 @@
+#!/bin/bash
+#MNH_LIC Copyright 1994-2023 CNRS, Meteo-France and Universite Paul Sabatier
+#MNH_LIC This is part of the Meso-NH software governed by the CeCILL-C licence
+#MNH_LIC version 1. See LICENSE, CeCILL-C_V1-en.txt and CeCILL-C_V1-fr.txt  
+#MNH_LIC for details. version 1.
+#SBATCH --job-name=compile_MNH
+#SBATCH -N 1 -n 1 -c 32
+#SBATCH -o Sortie_compile_MasterI.eo%j      
+#SBATCH --export=NONE
+#SBATCH -C GENOA
+#SBATCH --time 01:00:00
+#SBATCH -A mnh # put here your account/projet name
+
+set -x
+# On va lancer la compilation dans le répertoire de lancement du job
+pwd
+
+. ../conf/profile_mesonh-LXcray-R8I4-MNH-V5-6-1-MPICRAY-O2
+
+time make -j 32
+time make -j 1 installmaster
+