Jump to content
PDS Geosciences Node Community

stefano_to

Members
  • Posts

    1
  • Joined

  • Last visited

Posts posted by stefano_to

  1. Thanks for the code, it was quite useful to read ODF data files from several missions. On the other hand, I found several bugs (maybe ok for LP but not for other missions?), in particular regarding the reading of the Ramps (the first ramp table was sistematically skipped) and of the Reference Frequency (the formula was just wrong).

     

    Here below is an updated working version in Fortran (works with gfortran gcc version 4.7.2 20130108 on linux , should work also on other machines and compilers). It has been succesfully tested on GRAIL, Messenger and Mars Odyssey data. Hope it may be useful to other people! :)

    ( for questions or comments, please write me at stefano.bertone"at"aiub.unibe.ch )

    
    	PROGRAM ReadODF
    
    CCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCC
    
    C C
    
    C This program will transform the ODF format (described by the interface C
    
    C file trk-2-18) to ASCII records C
    
    C C
    
    C Created : SUN YU., 2010 - Shandong University of Science and Technology, Qingdao 266510, Shanddong Province, China C
    
    C C
    
    C Modifications : S.Bertone (2015) - AIUB, UniBern (CH): correction of reference frequency computation and ramps reading
    
    CCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCC
    
    
    
    
    
    C ------------ Begin of Data Type Definition------------------
    
    	IMPLICIT NONE
    
    	Integer*4 i,R,Iramp,ii
    
    	Integer*4 Idat_four(10),IRampG_four(10),IRampGH_four(10)
    
    	Integer*4 IOrbitG_four(10),IOrbitGH_four(10)
    
    	Real*8 RRange_M,RM_M,Rmout(19)
    
    	Integer*8 IOrbitG_eight(2)
    
    	Character*50 PrefixInputfile,Inputfile,TrimInputfile
    
    	Character*8 Char_eight(2)
    
    	Character*20 Char_twenty(2)
    
    	Logical Flag,Alive,exist
    
    
    
    C -------------End of Data Type Definition--------------------
    
    
    
    
    
    C ---------------Format-----------------
    
    105 	Format(F15.3,F15.10,F20.10,3I6,I4,2I5,6(1x,I3),1x,F17.3,I5,2I9)
    
    c108 Format(I15,f6.3,f22.10,2I4,I20,f20.5,F22.10,I4)
    
    c109 Format(I10,I10,3I5,2F25.10)
    
    c110 Format(2I10,2I5,2D25.14)
    
    C ---------------------------------------
    
    C Begin of executable codes
    
    CCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCC
    
    C Open binary files C
    
    C ODF files have eight independent data sections. All of them are C
    
    C in the form of binary,the format description is included in C
    
    C the interface file "trk-2-18" which is also provided together C
    
    C with the data. C
    
    C C
    
    C * Note C
    
    C To read this file, you need to notice what kind of work station C
    
    C or computer you are using in oder to figure out how the binary C
    
    C files are handled on your machine, it is either Big_endian(MSB) or C
    
    C Little_endian(LSB). For example, if you are using a PC, it would be C
    
    C Little_endian, but if it is a SUN work station, there is a good C
    
    C chance that it is Big_endian. C
    
    C C
    
    C In this case, we are running the program on a PC and we need to be C
    
    C aware that it is Little_endian. However, The LP ODF files cannot C
    
    C be recognized as you can see in the interface file that the data C
    
    C type is MSB_INTEGER. If you are using a Big_endian machine, there C
    
    C should be no problem. C
    
    C C
    
    C * How to solve this problem C
    
    C This problem can be easily solved by adding the OPTION C
    
    C "conver='big_endian'" in the OPEN STATMENT C
    
    C C
    
    CCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCC
    
    
    
    C Inputfile='./LPODF/lpodfcase1'
    
    	Write(6,*) ' ***********************'
    
    	Write(6,*)
    
    	Write(6,*) ' PROGRAM READ ODF '
    
    	Write(6,*)
    
    	Write(6,*) ' ***********************'
    
    	Write(6,*)
    
    	Write(6,*)
    
    	Write(6,*) ' -------------- INPUTFILE-------------'
    
    	Write(6,*) ' '
    
    	Write(6,*) ' Plese Select Inputfiles '
    
    	Write(6,*) ' From lpodfcase1 to 8 '
    
    	Write(6,*) ' '
    
    	Write(6,*) ' -------------------------------------'
    
    	Write(6,*)
    
    	Write(6,*)
    
    	Write(6,*) '-----------------------'
    
    	Write(6,*) ' The Input file is:'
    
    C Read (*,*) Inputfile
    
    	Inputfile='2340341a.odf'
    
    	PrefixInputfile='./'//Inputfile
    
    
    
    	TrimInputfile=PrefixInputfile(1:Len(Trim(PrefixInputfile)))
    
    	Write(6,*) '------------------------'
    
    	Write(6,*) 'The ODF file selected is'
    
    	write(*,*) TrimInputfile
    
    	Inquire(file=TrimInputfile,exist=Alive)
    
    	If (alive) Then
    
    	Write(6,*) ' ----------------READIND--------------'
    
    	Write(6,*)
    
    	Write(6,*) ' Start to read file ','Inputfile',
    
         1  ' '
    
    	Write(6,*)
    
    	Write(6,*) ' -------------------------------------'
    
    	Flag=Alive
    
    	Else
    
    	Write(6,*) ' -----------------ERROR---------------'
    
    	Write(6,*)
    
    	Write(6,*) ' The Inputfile dose not exist '
    
    	Write(6,*) ' Please check the Inputfile '
    
    	Write(6,*)
    
    	Write(6,*) ' -------------------------------------'
    
    	Stop
    
    	Endif
    
    
    
    	If (Flag) Then
    
    	Open(10,file=TrimInputfile,convert='big_endian',
    
         1  form='unformatted', access='direct',recl=36)
    
    
    
    C Open the OUTPUT files
    
    	Open(20,file='2340341a.asc')
    
    C First, the first 4 records we be read and write out
    
    C !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    
    C Record 1:ODF lable group header
    
    	Read(10,rec=1) (Idat_four(i),i=1,9)
    
    
    
    	Write(20,*) 'LPODF ASCII OUTPUT:'
    
    	Write(20,*) '=====================================',
    
         1  '=============='
    
    	Write(20,*) '----------Label Group: Header Record-',
    
         1  '--------------'
    
    	Write(20,*) 'Prime_Key Second_Key Log_Rec_Len',
    
         1  'Gp_St_Pkt_No'
    
    	Write(20,'(I8,2X,I8,6X,I8,8X,I8)') (Idat_four(i),i=1,4)
    
    	Write(20,*) '----------------------Data-----------',
    
         1  '--------------'
    
    	Write(6,*)
    
    	Write(6,*) ' Label Group: Header Record'
    
    	Endif
    
    
    
    C Record 2: ODF lable group
    
    	Read(10,rec=2) (Char_eight(i),i=1,2),(Idat_four(i),i=1,5)
    
    	Write(20,*) 'SystemID ProgramID SCID CrDate CrTime
    
         1 	FRefDate FRefTime'
    
    	Write(20,'(A10,A9,I6,I8,X,I8,3X,I8,3X,I6.6)')
    
         1 	(Char_eight(i),i=1,2),(Idat_four(i),i=1,5)
    
    	Write(20,*) '======================================',
    
         1  '=============='
    
    	Write(6,*)
    
    	Write(6,*) ' Label Group Data'
    
    
    
    C Record 3:ODF identifier goup header
    
    	Read(10,rec=3) (Idat_four(i),i=1,9)
    
    	Write(20,*) '--------Identifier Group: Hearder Record-',
    
         1  '--------------'
    
    	Write(20,*) 'Prime_Key Second_Key Log_Rec_Len',
    
         1  'Gp_St_Pkt_No'
    
    	Write(20,'(I8,2X,I8,6X,I8,8X,I8)') (Idat_four(i),i=1,4)
    
    	Write(20,*) '----------------------Data-----------',
    
         1  '--------------'
    
    	Write(6,*)
    
    	Write(6,*) ' Identifier Group:Header Record'
    
    
    
    C Record 4: ODF identifier goup data
    
    	Read(10,rec=4) (Char_eight(i),i=1,2),Char_twenty(1)
    
    	Write(20,*) ' Item_1 Item_2 Item_3'
    
    	Write(20,'(4X,A8,3X,A8,5X,A20)')
    
         1 (Char_eight(i),i=1,2),Char_twenty(1)
    
    	Write(20,*) '======================================',
    
         1	'=============='
    
    	Write(6,*)
    
    	Write(6,*) ' Identifier Group Data'
    
    
    
    C !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    
    	R=5
    
    	Do While (.True.) !This program will never stop
    
    	Read(10,rec=R) Idat_four(1) !unless you tell them to
    
    
    
    C       Go back to check when new Index is found (2030 in this case => should go into ramps)
    
    4444    CONTINUE
    
    
    
    	If (Idat_four(1).EQ.-1) Then !-1 means the EOF
    
    	Read(10,rec=R) (Idat_four(i),i=1,9) !we always have to figure whether
    
    !it's the end of the data file
    
    	Write(20,*)'--------End of File Group: Hearder Record',
    
         1  '------------'
    
    	Write(20,*) 'Prime_Key Second_Key Log_Rec_Len',
    
         1  'Gp_St_Pkt_No'
    
    	Write(20,'(I8,2X,I8,6X,I8,8X,I8)') (Idat_four(i),i=1,4)
    
    	Write(20,*) '----------------------Data-----------',
    
         1  '--------------'
    
    	Write(6,*)
    
    	Write(6,*) ' End of the ODF file'
    
    	Goto 9999 !if it is the end of the data file
    
    !then read the End of File Group
    
    !and write it done, after that,exit
    
    
    
    C!!!!!!!!!!!!!!!!!!!!!!! Reading the Orbit Data Group !!!!!!!!!!!!!!!!!!!!!!
    
    	Elseif (Idat_four(1).EQ.109) Then !find out if it is the Orbit Data
    
    !Group.
    
    
    
    3333 	Read(10,rec=R) (IOrbitGH_four(i),i=1,9)
    
    	Write(20,*) '----------Orbit Data Group: Header Record',
    
         1  '------------'
    
    	Write(20,*) 'Prime_Key Second_Key Log_Rec_Len
    
         1Gp_St_Pkt_No'
    
    	Write(20,'(I8,2X,I8,6X,I8,8X,I8)') (IOrbitGH_four(i),i=1,4)
    
    	Write(20,*) '----------------------Data-----------',
    
         1  '--------------'
    
    	Write(6,*)
    
    	Write(6,*) ' Orbit Data Group: Header'
    
    	Write(6,*)
    
    	Write(6,*) ' Orbit Data Group'
    
    	Write(20,'(A12,A15,A20,A10,2A6,A4,A6,7(A3,1x),A17,3A8)')
    
         1	'Time Tag', 'DL_delay','Observable','Fmt','DSSr','DSSt','Net',
    
         2	'D_Typ','DL','UL','Ex','V','2S','SC','17',
    
         3	'Reference Freq','Item_20','Item_21','Item_22'
    
    	R=R+1 !if it is the Orbit Data Group,
    
    	!write out the Header first. after
    
    	!the Header is the data group,
    
    	!read these data and write out
    
    	!till the EOF
    
    	Do While (.True.)
    
    	Read(10,rec=R) Idat_four(1)
    
    
    
    	If (Idat_four(1).EQ.-1) Then
    
    	Read(10,rec=R) (Idat_four(i),i=1,9)
    
    	Write(20,*)'--------End of file Group: Header Record',
    
         1  '------------'
    
    	Write(20,*) 'Prime_Key Second_Key Log_Rec_Len
    
         1 	Gp_St_Pkt_No'
    
    	Write(20,'(I8,2X,I8,6X,I8,8X,I8)') (Idat_four(i),i=1,4)
    
    	Write(20,*) '----------------------Data-----------',
    
         1  '--------------'
    
    	Write(6,*)
    
    	Write(6,*) ' End of the ODF file'
    
    	Goto 9999
    
    	Elseif (Idat_four(1).EQ.109) Then !this is in case there is more
    
    	!than one Orbit Data Group,
    
    	!though, there should be only one
    
    	Goto 3333
    
    	Elseif (Idat_four(1).EQ.2030) Then
    
    	  Goto 4444
    
    	Else
    
    
    
    	Read(10,rec=R) (IOrbitG_four(i),i=1,5),(IOrbitG_eight(i),i=1,2)
    
    
    
    	Write(20,105)
    
         1	IOrbitG_four(1)+ibits(IOrbitG_four(2),22,10)*1.D-3, !Record Time Tag
    
         3	ibits(IOrbitG_four(2),0,22)*1.D-9, !Downlink_delay
    
         4	IOrbitG_four(3)+IOrbitG_four(4)*1.D-9, !Observable
    
         5	ibits(IOrbitG_four(5),29,3), !Format ID=2
    
         5	ibits(IOrbitG_four(5),22,7), !Receiving Station ID NO.--DSSr
    
         5	ibits(IOrbitG_four(5),15,7), !Transmittiong Station ID NO.--DSSt
    
         5	ibits(IOrbitG_four(5),13,2), !Network ID for Transmitting Station
    
         5	ibits(IOrbitG_four(5),7,6), !Data Type ID.--D_Typ
    
         5	ibits(IOrbitG_four(5),5,2), !Downlink band ID.--DL
    
         5	ibits(IOrbitG_four(5),3,2), !Uplink band ID.--UL
    
         5	ibits(IOrbitG_four(5),1,2), !Exciter band ID.--Ex
    
         5	ibits(IOrbitG_four(5),0,1), !Data Validity Indicator (0 for good)
    
         6	ibits(IOrbitG_eight(1),57,7), !2nd Receiving station ID
    
         6	ibits(IOrbitG_eight(1),47,10), !Spacecraft ID
    
         6	ibits(IOrbitG_eight(1),46,1), !Receiver/Exciter Independet flag(1:yes)
    
         6	(ibits(IOrbitG_eight(1),24,22)*(2.d0**24)+
    
         6	ibits(IOrbitG_eight(1),0,24))*1.d-3, !Reference Frequency
    
         7	ibits(IOrbitG_eight(2),44,20), !
    
         7	ibits(IOrbitG_eight(2),22,22), !Compression Time s/100
    
         7	ibits(IOrbitG_eight(2),0,22) !
    
    	Endif
    
    
    
    	R=R+1
    
    	Enddo
    
    C     the most important data needed in
    
    C     the ODF file is the Orbit Data Groups
    
    C     and there should be only one of them
    
    C     in each ODF file.
    
    
    
    C!!!!!!!!!!!!!!!!!!! Reading the Ramp Group !!!!!!!!!!!!!!!!!!!!!!!!!!
    
    	Elseif (Idat_four(1).EQ.2030) Then !if it is not the EOF, then find
    
    !out if it is the Ramp Group.
    
    
    
    	Iramp=1
    
    
    
    2222 	Read(10,rec=R) (IRampGH_four(i),i=1,9)
    
    
    
    	Write(20,*) '-----------Ramp Group: Header Record-',
    
         1	'--------------'
    
    	Write(20,*) 'Prime_Key Second_Key Log_Rec_Len
    
         1 	Gp_St_Pkt_No'
    
    	Write(20,'(I8,2X,I8,6X,I8,8X,I8)') (IRampGH_four(i),i=1,4)
    
    	Write(20,*) '----------------------Data-----------',
    
         1	'--------------'
    
    	Write(6,*)
    
    	Write(6,*) ' Ramp Group',Iramp
    
    	Iramp=Iramp+1
    
    	Write(20,'(A5,A23,A18,2A21)')
    
         1	'DSS', 'Ramp Start Time','Ramp Rate',
    
         2	'Start Frequency','Ramp End Time'
    
    	R=R+1 !if it is the Ramp Group, then
    
    C              write out the Header first. after
    
    C              the Header is the data group,
    
    C              read these ramp data and write out
    
    C              till the EOF
    
    	Do While (.True.)
    
    	Read(10,rec=R) Idat_four(1)
    
    
    
    	If (Idat_four(1).EQ.-1) Then
    
    	Read(10,rec=R) (Idat_four(i),i=1,9)
    
    	Write(20,*)'--------End of file Group: Header Record',
    
         1	'-----------'
    
    	Write(20,*) 'Prime_Key Second_Key Log_Rec_Len',
    
         1 	            'Gp_St_Pkt_No'
    
    	Write(20,'(I8,2X,I8,6X,I8,8X,I8)') (Idat_four(i),i=1,4)
    
    	Write(20,*) '----------------------Data-----------',
    
         1	'--------------'
    
    	Write(6,*)
    
    	Write(6,*) ' End of the ODF file'
    
    	Goto 9999
    
    	Elseif (Idat_four(1).EQ.2030) Then !there is more than one ramp group
    
    	!in an ODF file.
    
    	Goto 2222
    
    	Else
    
    	Read(10,rec=R) (IRampG_four(i),i=1,9)
    
    
    
    	Write(20,'(I4,F25.10,F18.10,2F23.10)')
    
         1        ibits(IrampG_four(5),0,10),
    
         2	(IRampG_four(1)+IRampG_four(2)*1.D-9),
    
         3	IRampG_four(3)+IRampG_four(4)*1.D-9,
    
         4	ibits(IRampG_four(5),10,22)*1.D9+IRampG_four(6)+
    
         4	IRampG_four(7)*1.D-9,
    
         5	(IRampG_four(8)+IRampG_four(9)*1.D-9)
    
    	Endif
    
    	R=R+1
    
    	Enddo
    
    
    
    	Endif
    
    	R=R+1
    
    	Enddo
    
    
    
    	Close(10)
    
    	Close(20)
    
    
    
    9999 	Continue
    
    	End Program 
    
    
×
×
  • Create New...