Skip to content
Open
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
7 changes: 2 additions & 5 deletions source/calcul_Lstar_o.f
Original file line number Diff line number Diff line change
Expand Up @@ -80,6 +80,7 @@ SUBROUTINE calcul_Lstar_opt(t_resol,r_resol,
common /rconst/rad,pi
C
C
Ilflag = 0
Nder=Nder_def*r_resol
Nreb=Nreb_def
Ntet=Ntet_def*t_resol
Expand Down Expand Up @@ -286,14 +287,10 @@ SUBROUTINE calcul_Lstar_opt(t_resol,r_resol,
phi(I) = phi(I-1)+2.D0*pi/Nder
Iflag_I = 0
c write(6,*)tet(I)
IF (Ilflag.EQ.0) THEN
tetl = tet(I-1)
IF (I.GT.2) tetl = 2.D0*tet(I-1)-tet(I-2)
tet1 = tetl
ELSE
tetl = tet(I)
tet1 = tetl
ENDIF

c write(6,*)tetl
c read(5,*)
leI1 = baddata
Expand Down
11 changes: 1 addition & 10 deletions source/onera_desp_lib.f
Original file line number Diff line number Diff line change
Expand Up @@ -64,7 +64,7 @@ SUBROUTINE make_lstar1(ntime,kext,options,sysaxes,iyearsat,
c
c Declare internal variables
INTEGER*4 isat,iyear,kint,ifail
INTEGER*4 t_resol,r_resol,Ilflag,Ilflag_old
INTEGER*4 t_resol,r_resol
REAL*8 mlon,mlon1
REAL*8 xGEO(3),xMAG(3),xSUN(3),rM,MLAT
real*8 alti,lati,longi
Expand All @@ -75,12 +75,9 @@ SUBROUTINE make_lstar1(ntime,kext,options,sysaxes,iyearsat,
REAL*8 Lm(ntime_max),Lstar(ntime_max)
C
COMMON /magmod/k_ext,k_l,kint
COMMON /flag_L/Ilflag
DATA xSUN /1.d0,0.d0,0.d0/
integer*4 int_field_select, ext_field_select
C
Ilflag=0
Ilflag_old=Ilflag
if (options(3).lt.0 .or. options(3).gt.9) options(3)=0
t_resol=options(3)+1
r_resol=options(4)+1
Expand Down Expand Up @@ -132,12 +129,6 @@ SUBROUTINE make_lstar1(ntime,kext,options,sysaxes,iyearsat,
c
CALL calcul_Lstar_opt(t_resol,r_resol,XGeo
& ,Lm(isat),Lstar(isat),XJ(isat),BLOCAL(isat),BMIN(isat))
if (Ilflag_old .eq.1 .and. Lstar(isat).eq. Baddata) then
Ilflag=0
CALL calcul_Lstar_opt(t_resol,r_resol,xGeo
& ,Lm(isat),Lstar(isat),XJ(isat),BLOCAL(isat),BMIN(isat))
endif
Ilflag_old=Ilflag

99 continue

Expand Down
Loading