Whilst the DAL data model is independent of any underlying representation, there is an exceptional facility for handling the notion of the FITS Primary Image. An array with block number zero, and name "PRIMARY", will be treated by the FITS file reader/writer as the FITS primary image. This does not spoil the purety of the DAL data model, with FITS specific notions, since the interpretation, is made by the FITS File reader/writer, which is a separate piece of software, which is implementated, in terms of the abstract DAL interface. The restriction of setting the block number to zero, is needed to ensure consistancy of block numbers, between successive create and reads.
The name, units and comment may be changed. The type, dimensions and position may not be changed. In the event that the ordinal position is not at the end, the newly created array is inserted, moving subsequent blocks as necessary.
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! In this example add dataset is created (opened) containing
! two 3-dimensional arrays.
!
! It illustrates the use of the derived types DataSetT and ArrayT.
!
! The second array has the same data type as the first; this
! is ensured by using the arrayDataType() function to determine
! the data type of the first array.
!
! The first array is filled with unique data before the
! dataset is released (closed).
program example_addarray
use dal
use errorhandling
implicit none
type(DataSetT) set
type(ArrayT) arr1, arr2
integer(kind=int32), dimension(:,:,:), pointer :: a1, a2
integer, dimension(3), parameter :: s = (/ 3,4,2 /)
integer :: i,j,k,n
! create a set
set = dataSet("test.dat",CREATE)
arr1 = addArray(set, "array1", INTEGER32, dimensions=s )
arr2 = addArray(set, "array2", arrayDataType( arr1 ), dimensions=s )
! fill with unique numbers
a1 => int32Array3Data(arr1)
a2 => int32Array3Data(arr1)
n = 0
do k=0,1
do j=0,3
do i=0,2
a1(i,j,k) = n
a2(i,j,k) = a1(i,j,k) + 1
n = n + 1
end do
end do
end do
call release(arr1)
call release(arr2)
call release(set)
end program example_addarray
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
program example_addattributes
use dal
use errorhandling
implicit none
type(DataSetT) set
type(TableT) tab
set = dataSet("test.dat",CREATE)
call setAttribute(set,"sbool1",.false.,"dataset bool comment")
call setAttribute(set,"sbool2",.false.,"dataset bool comment")
tab = addTable(set,"table",10);
call addAttributes(attributable(tab),attributable(set))
call release(tab)
call release(set)
end program example_addattributes
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
program example_addcolumn
use dal
implicit none
type(DataSetT) set
type(TableT) tab
type(ColumnT) col
logical(kind=bool), dimension(:), pointer :: b
integer(kind=int8), dimension(:), pointer :: i8
integer(kind=int16), dimension(:), pointer :: i16
integer(kind=int32), dimension(:), pointer :: i32
real(kind=single), dimension(:), pointer :: r32
real(kind=double), dimension(:), pointer :: r64
character(len=1024) :: s
integer i
set = dataSet("test.dat",CREATE)
tab = addTable(set,"some table",100)
col = addColumn(tab,"bool",BOOLEAN)
b => boolData(col)
do i=0,numberOfRows(tab)-1
b(i) = ( modulo (i,2) .eq. 0 )
end do
col = addColumn(tab,"int8",INTEGER8,units="cm",comment="int8 column")
i8 => int8Data(col)
write(*,*) shape(i8)
do i=0,numberOfRows(tab)-1
i8(i) = i
end do
col = addColumn(tab,"int16",INTEGER16,units="dm",comment="int16 column")
i16 => int16Data(col)
do i=0,numberOfRows(tab)-1
i16(i) = 2*i
end do
col = addColumn(tab,"int32",INTEGER32,units="m",comment="in32 column")
i32 => int32Data(col)
do i=0,numberOfRows(tab)-1
i32(i) = 3*i
end do
col = addColumn(tab,"real32",REAL32,units="Dm",comment="real32 column")
r32 => real32Data(col)
do i=0,numberOfRows(tab)-1
r32(i) = 0.5*i
end do
col = addColumn(tab,"real64",REAL64,units="hm",comment="real64 column")
r64 => real64Data(col)
do i=0,numberOfRows(tab)-1
r64(i) = 0.25*i
end do
col = addColumn(tab,"string",STRING,comment="string column",dimensions=(/80/))
do i=0,numberOfRows(tab)-1
write(s,*) "string",i
call setStringCell(col,i,s)
end do
call release(set)
end program example_addcolumn
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
program example_addcomment
use dal
implicit none
type(DataSetT) set
type(TableT) tab
set = dataSet("test.dat",CREATE)
call addComment(set,"this comment is a dataset comment" )
call addComment(set,"and so is this one." )
tab = addTable(set,"some table",100)
call addComment(tab,"this comment is a table comment" )
call addComment(tab,"and so is this one." )
call addComment(block(set,0,MODIFY),"Another table comment")
call release(set)
end program example_addcomment
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
program example_addhistory
use dal
implicit none
type(DataSetT) set
type(TableT) tab
set = dataSet("test.dat",CREATE)
call addHistory(set,"this history is a dataset history" )
call addHistory(set,"and so is this one." )
tab = addTable(set,"some table",100)
call addHistory(tab,"this history is a table history" )
call addHistory(tab,"and so is this one." )
call addHistory(block(set,0,MODIFY),"Another table history")
call release(set)
end program example_addhistory
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! This example shows how the addtable()
! function is used.
program example_addtable
use dal
implicit none
type(DataSetT) set
type(TableT) tab
type(BlockT) blk
integer i
set = dataSet("test.dat",CREATE)
tab = addTable(set,"table1",10)
tab = addTable(set,"table2",100)
tab = addTable(set,"table3",1000)
do i=0,numberOfBlocks( set ) - 1
blk = block( set, i, MODIFY )
write(*,*) name( blk )
call addComment( blk, "A table comment" )
end do
call release(set)
end program example_addtable
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! In this example, a dataset is created containing
! a 3-dimensional array. The array is filled with unique
! numbers, before the dataset is released (closed).
!
! The dataset is then reopened (with READ access),
! and the array's data is displayed.
program example_array
use dal
use errorhandling
implicit none
type(DataSetT) set
type(ArrayT) arr
integer(kind=int32), dimension(:,:,:), pointer :: a
integer(kind=int32), dimension(:), pointer :: ad
integer, dimension(3), parameter :: s = (/ 3,4,2 /)
integer :: i,j,k,n
! create a set
set = dataSet("test.dat",CREATE)
arr = addArray(set, "some array", INTEGER32, dimensions=s )
! fill with unique numbers
a => int32Array3Data(arr)
n = 0
do k=0,1
do j=0,3
do i=0,2
a(i,j,k) = n
n = n + 1
end do
end do
end do
call release(arr)
call release(set)
! create a set
set = dataSet("test.dat",READ)
arr = array(set, "some array", READ)
ad => int32Data( arr )
do n = 0, numberOfElements( arr ) - 1
write(*,*) ad( n )
end do
call release(set)
end program example_array
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! In this example add dataset is created containing
! 2 arrays and 2 tables.
!
! A simple loop then iterates over the dataset's
! blocks printing appropriate messages.
! The first two blocks will have ARRAY_BLOCK block type.
! The second two blocks will have TABLE_BLOCK block type.
program example_blocktype
use dal
use errorhandling
implicit none
type(DataSetT) set
type(ArrayT) arr
type(TableT) tab
type(BlockT) blk
integer, dimension(3), parameter :: s = (/ 3,4,2 /)
integer :: i
! create a set
set = dataSet("test.dat",CREATE)
arr = addArray(set, "block0", INTEGER32, dimensions=s )
arr = addArray(set, "block1", INTEGER32, dimensions=s )
tab = addTable(set, "block2", 5 )
tab = addTable(set, "block3", 5 )
do i = 0, numberOfBlocks( set ) - 1
blk = block( set, i, READ )
if( blockType( block( set, i, READ ) ) .eq. ARRAY_BLOCK ) then
write(*,*) "The block with name ", name( blk ), " is an array."
arr = array( set, i, READ )
write(*,*) "It has ", numberOfDimensions( arr ), " dimensions."
end if
if( blockType( block( set, i, READ ) ) .eq. TABLE_BLOCK ) then
write(*,*) "The block with name ", name( blk ), " is a table."
tab = table( set, i )
write(*,*) "It has ", numberOfRows( tab ), " rows."
end if
end do
call release(arr)
call release(set)
end program example_blocktype
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! In this example add dataset is created (opened) containing
! two 3-dimensional arrays.
!
! It illustrates the use of the derived types DataSetT and ArrayT.
!
! The second array has the same data type as the first; this
! is ensured by using the arrayDataType() function to determine
! the data type of the first array.
!
! The first array is filled with unique data before the
! dataset is released (closed).
program example_addarray
use dal
use errorhandling
implicit none
type(DataSetT) set
type(ArrayT) arr1, arr2
integer(kind=int32), dimension(:,:,:), pointer :: a1, a2
integer, dimension(3), parameter :: s = (/ 3,4,2 /)
integer :: i,j,k,n
! create a set
set = dataSet("test.dat",CREATE)
arr1 = addArray(set, "array1", INTEGER32, dimensions=s )
arr2 = addArray(set, "array2", arrayDataType( arr1 ), dimensions=s )
! fill with unique numbers
a1 => int32Array3Data(arr1)
a2 => int32Array3Data(arr1)
n = 0
do k=0,1
do j=0,3
do i=0,2
a1(i,j,k) = n
a2(i,j,k) = a1(i,j,k) + 1
n = n + 1
end do
end do
end do
call release(arr1)
call release(arr2)
call release(set)
end program example_addarray
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! In this example, a dataset is created with one table and one
! array.
! Two attributes are added to each of the dataset, table and array.
!
! The generic subroutine displayAttributes, which operates on the
! AttributableT base type, displays the attributes contained in
! each of the dataset, table and array.
subroutine displayAttributes( thisAttributable )
use dal
implicit none
type(AttributableT) thisAttributable
type(AttributeT) att
integer i
do i = 0, numberOfAttributes( thisAttributable ) - 1
att = attribute( thisAttributable, i )
write(*,*) name( att ), stringAttribute( att ), units( att ), label( att )
end do
end subroutine displayAttributes
program example_attributable
use dal
implicit none
type(DataSetT) set
type(TableT) tab
type(ArrayT) arr
integer(kind=int32), dimension(:,:,:), pointer :: a
integer, dimension(3), parameter :: s = (/ 3,4,2 /)
set = dataSet("test.dat",CREATE)
call setAttribute(set,"sbool1",.false.,"dataset first bool comment")
call setAttribute(set,"sbool2",.true.,"dataset second comment")
tab = addTable(set,"table",10);
call setAttribute(set,"int1",1,"table first integer comment","kg")
call setAttribute(set,"int2",2,"table second integer comment","mm")
arr = addArray(set, "array", INTEGER32, dimensions=s )
call setAttribute(set,"real1",1.1,"array first real comment","kN")
call setAttribute(set,"real2",2.3,"array second real comment","rad")
call displayAttributes( attributable( set ) )
call displayAttributes( attributable( tab ) )
call displayAttributes( attributable( arr ) )
call release(set)
end program example_attributable
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! In this example a dataset with a table is ! created.
! Two attributes are added to each of the dataset ! and table.
! The attribute names of the dataset are displayed using
! access-by-number, and the table attribute names are displayed
! using access-by-name.
program example_attribute
use dal
implicit none
type(DataSetT) set
type(TableT) tab
type(ArrayT) arr
set = dataSet("test.dat",CREATE)
call setAttribute(set,"sbool1",.false.,"dataset bool comment")
call setAttribute(set,"sbool2",.true.,"dataset bool comment")
tab = addTable(set,"table",10);
call setAttribute(tab,"sbool1",.false.,"table bool comment")
call setAttribute(tab,"sbool2",.true.,"table bool comment")
write(*,*) name( attribute( set, 0 ))
write(*,*) name( attribute( set, 1 ))
write(*,*) name( attribute( tab, "sbool1" ))
write(*,*) name( attribute( tab, "sbool2" ))
call release(set)
end program example_attribute
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! In this example, a dataset is created with one table and one
! array.
! The generic subroutine displayBlock, which operates on the
! BlockT base type. The blockType() function operates on objects
! of type BlockT.
! The example also sjows blocks being retrieved from the dataset
! both by name and by number.
subroutine displayBlock( thisBlock )
use dal
implicit none
type(BlockT) thisBlock
write(*,*) "The block with name ", name( thisBlock )
if( blockType( thisBlock ) .eq. ARRAY_BLOCK ) then
write(*,*) " is an array."
end if
if( blockType( thisBlock ) .eq. TABLE_BLOCK ) then
write(*,*) " is a table."
end if
end subroutine displayBlock
subroutine displayBlocks( thisSet )
use dal
implicit none
type(DataSetT) thisSet
integer i
do i = 0, numberOfBlocks( thisSet ) - 1
call displayBlock( block( thisSet, i, READ ) )
end do
end subroutine displayBlocks
program example_block
use dal
implicit none
type(DataSetT) set
type(TableT) tab
type(ArrayT) arr
integer, dimension(3), parameter :: s = (/ 3,4,2 /)
set = dataSet("test.dat",CREATE)
tab = addTable(set,"table",10);
arr = addArray(set, "array", INTEGER32, dimensions=s )
call displayBlock( block( tab ) )
call displayBlock( block( arr ) )
call displayBlock( block( set, "table", READ ) )
call displayBlock( block( set, "array", READ ) )
call displayBlocks( set )
call release(set)
end program example_block
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! In this example, a dataset is created with one table and one
! array.
! The generic subroutine displayBlock, which operates on the
! BlockT base type. The blockType() function operates on objects
! of type BlockT.
! The example also sjows blocks being retrieved from the dataset
! both by name and by number.
subroutine displayBlock( thisBlock )
use dal
implicit none
type(BlockT) thisBlock
write(*,*) "The block with name ", name( thisBlock )
if( blockType( thisBlock ) .eq. ARRAY_BLOCK ) then
write(*,*) " is an array."
end if
if( blockType( thisBlock ) .eq. TABLE_BLOCK ) then
write(*,*) " is a table."
end if
end subroutine displayBlock
subroutine displayBlocks( thisSet )
use dal
implicit none
type(DataSetT) thisSet
integer i
do i = 0, numberOfBlocks( thisSet ) - 1
call displayBlock( block( thisSet, i, READ ) )
end do
end subroutine displayBlocks
program example_block
use dal
implicit none
type(DataSetT) set
type(TableT) tab
type(ArrayT) arr
integer, dimension(3), parameter :: s = (/ 3,4,2 /)
set = dataSet("test.dat",CREATE)
tab = addTable(set,"table",10);
arr = addArray(set, "array", INTEGER32, dimensions=s )
call displayBlock( block( tab ) )
call displayBlock( block( arr ) )
call displayBlock( block( set, "table", READ ) )
call displayBlock( block( set, "array", READ ) )
call displayBlocks( set )
call release(set)
end program example_block
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! This example creates a dataset with one
! table and one array.
! The table will have block number 0,
! and the array will have block number 1
subroutine displayBlockNumber( thisBlock )
use dal
implicit none
type(BlockT) thisBlock
write(*,*) "The block with name ", name( thisBlock ), "has number "
write(*,*) blockNumber( parent( thisBlock ), name( thisBlock ) )
end subroutine displayBlockNumber
program example_blocknumber
use dal
implicit none
type(DataSetT) set
type(TableT) tab
type(ArrayT) arr
integer, dimension(3), parameter :: s = (/ 3,4,2 /)
set = dataSet("test.dat",CREATE)
tab = addTable(set,"table",10);
arr = addArray(set, "array", INTEGER32, dimensions=s )
call displayBlockNumber( block( tab ) )
call displayBlockNumber( block( arr ) )
call release(set)
end program example_blockNumber
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! In this example add dataset is created containing
! 2 arrays and 2 tables.
!
! A simple loop then iterates over the dataset's
! blocks printing appropriate messages.
! The first two blocks will have ARRAY_BLOCK block type.
! The second two blocks will have TABLE_BLOCK block type.
program example_blocktype
use dal
use errorhandling
implicit none
type(DataSetT) set
type(ArrayT) arr
type(TableT) tab
type(BlockT) blk
integer, dimension(3), parameter :: s = (/ 3,4,2 /)
integer :: i
! create a set
set = dataSet("test.dat",CREATE)
arr = addArray(set, "block0", INTEGER32, dimensions=s )
arr = addArray(set, "block1", INTEGER32, dimensions=s )
tab = addTable(set, "block2", 5 )
tab = addTable(set, "block3", 5 )
do i = 0, numberOfBlocks( set ) - 1
blk = block( set, i, READ )
if( blockType( block( set, i, READ ) ) .eq. ARRAY_BLOCK ) then
write(*,*) "The block with name ", name( blk ), " is an array."
arr = array( set, i, READ )
write(*,*) "It has ", numberOfDimensions( arr ), " dimensions."
end if
if( blockType( block( set, i, READ ) ) .eq. TABLE_BLOCK ) then
write(*,*) "The block with name ", name( blk ), " is a table."
tab = table( set, i )
write(*,*) "It has ", numberOfRows( tab ), " rows."
end if
end do
call release(arr)
call release(set)
end program example_blocktype
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! This example shows how boolean attributes are used.
! The program creates a dataset containing two boolean attributes,
! together with a table containing two boolean attributes.
! The attributes are then accessed, by name, with
! the booleanAttribute() function.
! Also, it is shown how to access the attributes by position.
program example_booleanattribute
use dal
use errorhandling
implicit none
type(DataSetT) set
type(TableT) tab
type(AttributeT) att
integer i
set = dataSet("test.dat",CREATE)
call setAttribute(set,"sbool1",.false.,"dataset bool comment")
call setAttribute(set,"sbool2",.true.,"dataset bool comment")
tab = addTable(set,"table",10);
call setAttribute(tab,"sbool1",.false.,"dataset bool comment")
call setAttribute(tab,"sbool2",.true.,"dataset bool comment")
write(*,*) booleanAttribute( set, "sbool1" ) ! output 'F'
write(*,*) booleanAttribute( set, "sbool2" ) ! output 'T'
write(*,*) booleanAttribute( tab, "sbool1" ) ! output 'F'
write(*,*) booleanAttribute( tab, "sbool2" ) ! output 'T'
do i = 0, numberOfAttributes( set ) - 1
att = attribute( set, i )
write(*,*) booleanAttribute( att ) ! output the sequence 'F','T'
end do
call release(set)
end program example_booleanattribute
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! In this example add dataset is created (opened) containing
! a table with 2 columns of two 2-dimensional arrays.
!
! The second array has the same data type as the first; this
! is ensured by using the arrayDataType() function to determine
! the data type of the first array.
!
! The columns are then initialised, on a row-by-row
! basis (i.e. accessing the column's data cell-by-cell),
! before the dataset is released (closed).
program example_cellarray2data
use dal
use errorhandling
implicit none
type(DataSetT) set
type(TableT) tab
type(ColumnT) col1, col2
logical(kind=BOOL), dimension(:,:), pointer :: c1, c2
integer, dimension(2), parameter :: s = (/ 3,4 /)
integer :: i,j,k,n
! create a set
set = dataSet("test.dat",CREATE)
tab = addTable(set, "table", 100, "table comment" )
col1 = addColumn( tab, "column1", BOOLEAN, "km", s, "column comment" )
col2 = addColumn( tab, "column2", columnDataType( col1 ), "km", s, "column comment" )
! fill with unique numbers
n = 0
do k=0,numberOfRows(tab) - 1
c1 => boolArray2Data(col1,k)
c2 => boolArray2Data(col2,k)
do j=0,3
do i=0,2
c1(i,j) = .false.
c2(i,j) = c1(i,j)
n = n + 1
end do
end do
end do
call release(col1)
call release(col2)
call release(set)
end program example_cellarray2data
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! In this example add dataset is created (opened) containing
! a table with 2 columns of two 2-dimensional arrays.
!
! The second array has the same data type as the first; this
! is ensured by using the arrayDataType() function to determine
! the data type of the first array.
!
! The columns are then initialised before the
! dataset is released (closed).
program example_array2data
use dal
use errorhandling
implicit none
type(DataSetT) set
type(TableT) tab
type(ColumnT) col1, col2
logical(kind=BOOL), dimension(:,:,:), pointer :: c1, c2
integer, dimension(2), parameter :: s = (/ 3,4 /)
integer :: i,j,k,n
! create a set
set = dataSet("test.dat",CREATE)
tab = addTable(set, "table", 100, "table comment" )
col1 = addColumn( tab, "column1", BOOLEAN, "km", s, "column comment" )
col2 = addColumn( tab, "column2", columnDataType( col1 ), "km", s, "column comment" )
! fill with unique numbers
c1 => boolArray2Data(col1)
c2 => boolArray2Data(col1)
n = 0
do k=0,numberOfRows(tab) - 1
do j=0,3
do i=0,2
c1(i,j,k) = .false.
c2(i,j,k) = c1(i,j,k)
n = n + 1
end do
end do
end do
call release(col1)
call release(col2)
call release(set)
end program example_array2data
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! In this example add dataset is created (opened) containing
! a table with 2 columns of two 3-dimensional arrays.
!
! The second array has the same data type as the first; this
! is ensured by using the arrayDataType() function to determine
! the data type of the first array.
!
! The columns are then initialised, on a row-by-row
! basis (i.e. accessing the column's data cell-by-cell),
! before the dataset is released (closed).
program example_cellarray3data
use dal
use errorhandling
implicit none
type(DataSetT) set
type(TableT) tab
type(ColumnT) col1, col2
logical(kind=BOOL), dimension(:,:,:), pointer :: c1, c2
integer, dimension(3), parameter :: s = (/ 3,4,5 /)
integer :: i,j,k,l,n
! create a set
set = dataSet("test.dat",CREATE)
tab = addTable(set, "table", 100, "table comment" )
col1 = addColumn( tab, "column1", BOOLEAN, "km", s, "column comment" )
col2 = addColumn( tab, "column2", columnDataType( col1 ), "km", s, "column comment" )
! fill with unique numbers
n = 0
do l=0,numberOfRows(tab) - 1
c1 => boolArray3Data(col1,l)
c2 => boolArray3Data(col2,l)
do k=0,4
do j=0,3
do i=0,2
c1(i,j,k) = .false.
c2(i,j,k) = c1(i,j,k)
n = n + 1
end do
end do
end do
end do
call release(col1)
call release(col2)
call release(set)
end program example_cellarray3data
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! In this example add dataset is created (opened) containing
! a table with 2 columns of two 3-dimensional arrays.
!
! The second array has the same data type as the first; this
! is ensured by using the arrayDataType() function to determine
! the data type of the first array.
!
! The columns are then initialised before the
! dataset is released (closed).
program example_array3data
use dal
use errorhandling
implicit none
type(DataSetT) set
type(TableT) tab
type(ColumnT) col1, col2
logical(kind=BOOL), dimension(:,:,:,:), pointer :: c1, c2
integer, dimension(3), parameter :: s = (/ 3,4,5 /)
integer :: i,j,k,l,n
! create a set
set = dataSet("test.dat",CREATE)
tab = addTable(set, "table", 100, "table comment" )
col1 = addColumn( tab, "column1", BOOLEAN, "km", s, "column comment" )
col2 = addColumn( tab, "column2", columnDataType( col1 ), "km", s, "column comment" )
! fill with unique numbers
c1 => boolArray3Data(col1)
c2 => boolArray3Data(col1)
n = 0
do l=0,numberOfRows(tab) - 1
do k = 0,4
do j=0,3
do i=0,2
c1(i,j,k,l) = .false.
c2(i,j,k,l) = c1(i,j,k,l)
n = n + 1
end do
end do
end do
end do
call release(col1)
call release(col2)
call release(set)
end program example_array3data
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! In this example add dataset is created (opened) containing
! a table with 2 columns of two 4-dimensional arrays.
!
! The second array has the same data type as the first; this
! is ensured by using the arrayDataType() function to determine
! the data type of the first array.
!
! The columns are then initialised, on a row-by-row
! basis (i.e. accessing the column's data cell-by-cell),
! before the dataset is released (closed).
program example_cellarray4data
use dal
use errorhandling
implicit none
type(DataSetT) set
type(TableT) tab
type(ColumnT) col1, col2
logical(kind=BOOL), dimension(:,:,:,:), pointer :: c1, c2
integer, dimension(4), parameter :: s = (/ 3,4,5,6 /)
integer :: i,j,k,l,m,n
! create a set
set = dataSet("test.dat",CREATE)
tab = addTable(set, "table", 100, "table comment" )
col1 = addColumn( tab, "column1", BOOLEAN, "km", s, "column comment" )
col2 = addColumn( tab, "column2", columnDataType( col1 ), "km", s, "column comment" )
! fill with unique numbers
n = 0
do m=0,numberOfRows(tab) - 1
c1 => boolArray4Data(col1,m)
c2 => boolArray4Data(col2,m)
do l=0,5
do k=0,4
do j=0,3
do i=0,2
c1(i,j,k,l) = .false.
c2(i,j,k,l) = c1(i,j,k,l)
n = n + 1
end do
end do
end do
end do
end do
call release(col1)
call release(col2)
call release(set)
end program example_cellarray4data
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! In this example add dataset is created (opened) containing
! a table with 2 columns of two 3-dimensional arrays.
!
! The second array has the same data type as the first; this
! is ensured by using the arrayDataType() function to determine
! the data type of the first array.
!
! The columns are then initialised before the
! dataset is released (closed).
program example_array3data
use dal
use errorhandling
implicit none
type(DataSetT) set
type(TableT) tab
type(ColumnT) col1, col2
logical(kind=BOOL), dimension(:,:,:,:), pointer :: c1, c2
integer, dimension(3), parameter :: s = (/ 3,4,5 /)
integer :: i,j,k,l,n
! create a set
set = dataSet("test.dat",CREATE)
tab = addTable(set, "table", 100, "table comment" )
col1 = addColumn( tab, "column1", BOOLEAN, "km", s, "column comment" )
col2 = addColumn( tab, "column2", columnDataType( col1 ), "km", s, "column comment" )
! fill with unique numbers
c1 => boolArray3Data(col1)
c2 => boolArray3Data(col1)
n = 0
do l=0,numberOfRows(tab) - 1
do k = 0,4
do j=0,3
do i=0,2
c1(i,j,k,l) = .false.
c2(i,j,k,l) = c1(i,j,k,l)
n = n + 1
end do
end do
end do
end do
call release(col1)
call release(col2)
call release(set)
end program example_array3data
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! In this example add dataset is created (opened) containing
! a table with 2 columns of two 4-dimensional arrays.
!
! The second array has the same data type as the first; this
! is ensured by using the arrayDataType() function to determine
! the data type of the first array.
!
! The columns are then initialised, and then the second column
! is output by accessing the column's data as a flat vector.
program example_booldata
use dal
use errorhandling
implicit none
type(DataSetT) set
type(TableT) tab
type(ColumnT) col1, col2
logical(kind=BOOL), dimension(:,:,:,:,:), pointer :: c1, c2
logical(kind=BOOL), dimension(:), pointer :: cd
integer, dimension(4), parameter :: s = (/ 3,4,5,6 /)
integer :: i,j,k,l,m,n
! create a set
set = dataSet("test.dat",CREATE)
tab = addTable(set, "table", 5, "table comment" )
col1 = addColumn( tab, "column1", BOOLEAN, "km", s, "column comment" )
col2 = addColumn( tab, "column2", columnDataType( col1 ), "km", s, "column comment" )
! fill with unique numbers
c1 => boolArray4Data(col1)
c2 => boolArray4Data(col2)
n = 0
do m=0,numberOfRows(tab) - 1
do l=0,5
do k=0,4
do j=0,3
do i=0,2
c1(i,j,k,l,m) = .false.
c2(i,j,k,l,m) = c1(i,j,k,l,m)
n = n + 1
end do
end do
end do
end do
end do
call release(col1)
call release(col2)
! Output the col2
cd => boolData( col2 ) ! Access the column's 4-dimensional data as a flat vector.
do n = 0,numberOfElements(col1) * numberOfRows(tab) - 1
write(*,*) cd(n)
end do
call release(col2)
call release(set)
end program example_booldata
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! In this example add dataset is created (opened) containing
! a table with 2 columns of two vector arrays.
!
! The second array has the same data type as the first; this
! is ensured by using the arrayDataType() function to determine
! the data type of the first array.
!
! The columns are then initialised, on a row-by-row
! basis (i.e. accessing the column's data cell-by-cell).
! The data is output on a cell-by-cell basis and accessing
! the cell as a flat vector.
program example_boolcellvectordata
use dal
use errorhandling
implicit none
type(DataSetT) set
type(TableT) tab
type(ColumnT) col1, col2
logical(kind=BOOL), dimension(:), pointer :: c1, c2
integer, dimension(1), parameter :: s = (/ 3 /)
integer :: i,m,n
! create a set
set = dataSet("test.dat",CREATE)
tab = addTable(set, "table", 100, "table comment" )
col1 = addColumn( tab, "column1", BOOLEAN, "km", s, "column comment" )
col2 = addColumn( tab, "column2", columnDataType( col1 ), "km", s, "column comment" )
! fill with unique numbers
n = 0
do m=0,numberOfRows(tab) - 1
c1 => boolVectorData(col1,m)
c2 => boolVectorData(col2,m)
do i=0,2
c1(i) = .false.
c2(i) = c1(i)
n = n + 1
end do
! release(col1)
! release(col2)
end do
! Output col2
do m=0,numberOfRows(tab) - 1
c2 => boolVectorData(col2,m)
do n=0,numberOfElements(col2) - 1
write(*,*) c2(n)
end do
! release(col2)
end do
call release(set)
end program example_boolcellvectordata
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! In this example add dataset is created (opened) containing
! a table with 2 columns of two vector arrays.
!
! The second array has the same data type as the first; this
! is ensured by using the columnDataType() function to determine
! the data type of the first array.
!
! The columns are then initialised before the
! dataset is released (closed).
program example_columnvectordata
use dal
use errorhandling
implicit none
type(DataSetT) set
type(TableT) tab
type(ColumnT) col1, col2
logical(kind=BOOL), dimension(:,:), pointer :: c1, c2
integer, dimension(1), parameter :: s = (/ 3 /)
integer :: i,j,k,l,m,n
! create a set
set = dataSet("test.dat",CREATE)
tab = addTable(set, "table", 100, "table comment" )
col1 = addColumn( tab, "column1", BOOLEAN, "km", s, "column comment" )
col2 = addColumn( tab, "column2", columnDataType( col1 ), "km", s, "column comment" )
! fill with unique numbers
c1 => boolVectorData(col1)
c2 => boolVectorData(col2)
n = 0
do m=0,numberOfRows(tab) - 1
do i=0,2
c1(i,m) = .false.
c2(i,m) = c1(i,m)
n = n + 1
end do
end do
call release(col1)
call release(col2)
call release(set)
end program example_columnvectordata
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! This example shows how the clobber() function is
! used.
program example_clobber
use dal
implicit none
if( clobber() ) then
write(*,*) "The SAS_CLOBBER environment variable is set"
else
write(*,*) "The SAS_CLOBBER environment variable is not set"
endif
end program example_clobber
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! This examples show how the column() function is used.
! The column by name is used to get a column and rename it.
! The column by number is used to iterate over all
! columns in the table to output the name, type and units.
program example_column
use dal
implicit none
type(DataSetT) set
type(TableT) tab
type(ColumnT) col
integer i
set = dataSet("test.dat",CREATE)
tab = addTable(set,"some table",100)
col = addColumn(tab,"col1",INTEGER32,units="m1",comment="in32 column")
col = addColumn(tab,"col2",INTEGER32,units="m2",comment="in32 column")
col = addColumn(tab,"col3",INTEGER32,units="m3",comment="in32 column")
col = column( tab, "col2", MODIFY )
call rename( col, "col4" )
do i =0, numberOfColumns( tab ) - 1
col = column( tab, i, READ )
write(*,*) name( col ), columnDataType( col ), units( col )
end do
call release(set)
end program example_column
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! This examples shows how the columnNumber() function
! is used.
program example_columnnumber
use dal
implicit none
type(DataSetT) set
type(TableT) tab
type(ColumnT) col
integer i
set = dataSet("test.dat",CREATE)
tab = addTable(set,"some table",100)
col = addColumn(tab,"int16",INTEGER16,units="dm",comment="int16 column")
col = addColumn(tab,"int32",INTEGER32,units="m",comment="in32 column")
col = addColumn(tab,"real32",REAL32,units="Dm",comment="real32 column")
col = addColumn(tab,"real64",REAL64,units="hm",comment="real64 column", &
position=columnNumber( tab, "int32" ) )
do i = 0, numberOfColumns( tab ) - 1
col = column( tab, i, READ )
write(*,*) name( col )
end do
call release(set)
end program example_columnnumber
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! In this example a dataset is created, with
! three tables.
!
! The created datanew is then copied to a new dataset.
! A simple loop then iterates over the
! dataset's blocks (a table may be treated as a block)
! Each block is copyied to a second dataset, and
! then displays the name of each new block (which actually
! will be the same name as the source block); a comment
! is added to each new block.
program example_copyblock
use dal
implicit none
type(DataSetT) set1, set2
type(TableT) tab
type(BlockT) blk
integer i
set1 = dataSet("test.dat",CREATE)
tab = addTable(set1,"first table",100)
tab = addTable(set1,"second table",1000)
tab = addTable(set1,"third table",10000)
set2 = dataSet("test1.dat",CREATE)
do i = 0, numberOfBlocks( set1 ) - 1
blk = block( set1, i, MODIFY )
call copyBlock( set2, blk )
blk = block( set2, i, MODIFY )
call addComment( blk, "Copied from test.dat" )
end do
call release(set1)
call release(set2)
end program example_copyblock
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! This examples show how to use the copyColumn function.
program example_copycolumn
use dal
implicit none
type(DataSetT) set1, set2
type(TableT) tab1, tab2
type(ColumnT) col1, col2, col3, col4
integer(kind=int32), dimension(:), pointer :: i32
real(kind=single), dimension(:), pointer :: r32
integer i
set1 = dataSet("test.dat",CREATE)
tab1 = addTable(set1,"some table",100)
col1 = addColumn(tab1,"col1",INTEGER32,units="m",comment="in32 column")
i32 => int32Data(col1)
do i=0,numberOfRows(tab1)-1
i32(i) = 3*i
end do
call release( col1)
col2 = addColumn(tab1,"col2",REAL32,units="Dm",comment="real32 column")
r32 => real32Data(col2)
do i=0,numberOfRows(tab1)-1
r32(i) = 0.5*i
end do
call release( col2)
set2 = dataSet("test1.dat",CREATE)
tab2 = addTable(set2,"some table",100)
call copyColumn( tab2, col1 )
call copyColumn( tab2, col2, "col3" )
col3 = column( tab2, name( col1 ), READ )
col4 = column( tab2, "col3", READ )
i32 => int32Data(col3)
r32 => real32Data(col4)
do i = 0, numberOfRows( tab2 ) - 1
write(*,*) i32(i), r32(i)
end do
call release(col3)
call release(col4)
call release(set1)
call release(set2)
end program example_copycolumn
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! In this example a dataset is created, with
! three tables.
! The created datanew is then copied to a new dataset.
! A simple loop then iterates over the new
! dataset's ! blocks (a table may be treated as a block)
! then displays the name of ! each table, and adds a comment
! to each block (table).
program example_copydataset
use dal
implicit none
type(DataSetT) set
type(TableT) tab
type(BlockT) blk
integer i
set = dataSet("test.dat",CREATE)
tab = addTable(set,"first table",100)
tab = addTable(set,"second table",1000)
tab = addTable(set,"third table",10000)
call release(set)
call copyDataSet( "test.dat", "test1.dat" )
set = dataSet("test1.dat",READ)
do i = 0, numberOfBlocks( set ) - 1
blk = block( set, i, MODIFY )
write(*,*) name( blk )
call addComment( blk, "Copied from test.dat" )
end do
call release(set)
end program example_copydataset
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! This example shows how to use the clone
! function.
program example_clone
use dal
implicit none
type(DataSetT) set
type(DataSetT) clonedSet
set = dataSet("test.dat",CREATE)
call setAttribute(set,"att1", 10, "mm", "attribute comment" )
call release(set)
set = dataSet("test.dat",MODIFY)
call setAttribute(set,"att1", 10, "mm", "attribute comment" )
call release(set)
clonedSet = clone("test.dat","test2.dat",MODIFY)
call setAttribute(clonedSet,"att2", 10, "mm", "attribute comment" )
call release(clonedSet)
set = dataSet("test2.dat",READ)
write(*,*) "att2 = ", int32Attribute( set, "att2" );
call release(set)
end program example_clone
Memory Considerations This operation of copying rows within a table is very expensive.
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! This examples show how to use the copyRows subroutine.
program example_copyrows
use dal
implicit none
type(DataSetT) set
type(TableT) tab
type(ColumnT) col1, col2
integer(kind=int32), dimension(:), pointer :: i32
real(kind=single), dimension(:), pointer :: r32
integer i
set = dataSet("test.dat",CREATE)
tab = addTable(set,"some table",10)
col1 = addColumn(tab,"col1",INTEGER32,units="m",comment="in32 column")
i32 => int32Data(col1)
do i=0,4
i32(i) = 3*i
end do
call release( col1)
col2 = addColumn(tab,"col2",REAL32,units="Dm",comment="real32 column")
r32 => real32Data(col2)
do i=0,4
r32(i) = 0.5*i
end do
call release( col2)
call copyRows( tab, 0, 5, 5 ) ! copy range [0,4] to [5,9]
i32 => int32Data(col1)
r32 => real32Data(col2)
do i = 0, numberOfRows( tab ) - 1
write(*,*) i32(i), r32(i)
end do
call release(col1)
call release(col2)
call release(set)
end program example_copyrows
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! This example shows how the seek functions
! are used.
! This subroutine will dispaly the seek values of the given table and column.
subroutine whatisseek(tab)
use dal
type(TableT), intent(in) :: tab
type(ColumnT) :: col
write(*,*) from( tab ), count( tab )
col = column(tab,"x",MODIFY)
write(*,*) from( col ), count( col )
end subroutine whatisseek
program example_seek
use dal
implicit none
type(DataSetT) :: set
type(TableT) :: tab
type(ColumnT) :: col
interface
subroutine whatisseek( subtab )
use dal
implicit none
type(TableT), intent(in) :: subtab
end subroutine whatisseek
end interface
set = dataSet("test.dat",CREATE)
tab = addTable(set,"events",10)
col = addColumn(tab,"x",real32,"mm")
call forEachSubTable(tab,whatisseek)
call release(set)
end program example_seek
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! This example illustrates the use of the dataComponent() function.
! The units of objects with data type BOOLEAN and STRING are meaningless
! and so are not displayed.
subroutine displayUnits( dcomponent )
use dal
implicit none
type(DataComponentT) dcomponent
integer dattype
dattype = dataType( dcomponent )
write(*,*) dattype
if(dattype.eq.INTEGER8.or.dattype.eq.INTEGER16.or.dattype.eq.INTEGER32 &
.or.dattype.eq.REAL32.or.dattype.eq.REAL64) then
write(*,*) units( dcomponent )
end if
end subroutine displayUnits
program example_datacomponent
use dal
implicit none
type(ArrayT) arr
type(BlockT) blk
type(ColumnT) col
type(DataSetT) set
type(TableT) tab
integer i, j
integer, dimension(3), parameter :: s = (/ 2,3,4 /)
set = dataSet("test.dat",CREATE)
tab = addTable(set,"some table",100)
col = addColumn(tab,"bool",BOOLEAN)
col = addColumn(tab,"int8",INTEGER8,units="cm",comment="int8 column")
col = addColumn(tab,"int16",INTEGER16,units="dm",comment="int16 column")
col = addColumn(tab,"int32",INTEGER32,units="m",comment="in32 column")
col = addColumn(tab,"real32",REAL32,units="Dm",comment="real32 column")
col = addColumn(tab,"real64",REAL64,units="hm",comment="real64 column")
col = addColumn(tab,"string",STRING,comment="string column",dimensions=(/80/))
arr = addArray(set, "array1", INTEGER16, dimensions=s, units="klm" )
arr = addArray(set, "array2", INTEGER32, dimensions=s, units="kla" )
do i = 0, numberOfBlocks( set ) - 1
blk = block( set, i, READ )
if( blockType( blk ).eq.ARRAY_BLOCK ) then
arr = array( set, name( blk ), READ )
call displayUnits( dataComponent( arr ) )
else
tab = table( set, name( blk ) )
do j = 0, numberOfColumns( tab ) - 1
col = column( tab, j, READ )
call displayUnits( dataComponent( col ) )
end do
end if
end do
call release(set)
end program example_datacomponent
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! This examp,e shows how to use the dataset
! function.
program example_dataset
use dal
implicit none
type(DataSetT) set
set = dataSet("test.dat",CREATE)
call setAttribute(set,"att1", 10, "mm", "attribute comment" )
call release(set)
set = dataSet("test.dat",MODIFY)
call setAttribute(set,"att1", 10, "mm", "attribute comment" )
call release(set)
set = dataSet("test.dat",READ)
write(*,*) "att1 = ", int32Attribute( set, "att1" )
call release(set)
end program example_dataset
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! In this example add dataset is created (opened) containing
! two 3-dimensional arrays.
!
! It illustrates the use of the derived types DataSetT and ArrayT.
!
! The second array has the same data type as the first; this
! is ensured by using the arrayDataType() function to determine
! the data type of the first array.
!
! The first array is filled with unique data before the
! dataset is released (closed).
program example_addarray
use dal
use errorhandling
implicit none
type(DataSetT) set
type(ArrayT) arr1, arr2
integer(kind=int32), dimension(:,:,:), pointer :: a1, a2
integer, dimension(3), parameter :: s = (/ 3,4,2 /)
integer :: i,j,k,n
! create a set
set = dataSet("test.dat",CREATE)
arr1 = addArray(set, "array1", INTEGER32, dimensions=s )
arr2 = addArray(set, "array2", arrayDataType( arr1 ), dimensions=s )
! fill with unique numbers
a1 => int32Array3Data(arr1)
a2 => int32Array3Data(arr1)
n = 0
do k=0,1
do j=0,3
do i=0,2
a1(i,j,k) = n
a2(i,j,k) = a1(i,j,k) + 1
n = n + 1
end do
end do
end do
call release(arr1)
call release(arr2)
call release(set)
end program example_addarray
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! This examples show how the column() function is used.
! The column by name is used to get a column and rename it.
! The column by number is used to iterate over all
! columns in the table to output the name, type and units.
program example_column
use dal
implicit none
type(DataSetT) set
type(TableT) tab
type(ColumnT) col
integer i
set = dataSet("test.dat",CREATE)
tab = addTable(set,"some table",100)
col = addColumn(tab,"col1",INTEGER32,units="m1",comment="in32 column")
col = addColumn(tab,"col2",INTEGER32,units="m2",comment="in32 column")
col = addColumn(tab,"col3",INTEGER32,units="m3",comment="in32 column")
col = column( tab, "col2", MODIFY )
call rename( col, "col4" )
do i =0, numberOfColumns( tab ) - 1
col = column( tab, i, READ )
write(*,*) name( col ), columnDataType( col ), units( col )
end do
call release(set)
end program example_column
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! This example illustrates the use of the dataComponent() function.
! The units of objects with data type BOOLEAN and STRING are meaningless
! and so are not displayed.
subroutine displayUnits( dcomponent )
use dal
implicit none
type(DataComponentT) dcomponent
integer dattype
dattype = dataType( dcomponent )
write(*,*) dattype
if(dattype.eq.INTEGER8.or.dattype.eq.INTEGER16.or.dattype.eq.INTEGER32 &
.or.dattype.eq.REAL32.or.dattype.eq.REAL64) then
write(*,*) units( dcomponent )
end if
end subroutine displayUnits
program example_datacomponent
use dal
implicit none
type(ArrayT) arr
type(BlockT) blk
type(ColumnT) col
type(DataSetT) set
type(TableT) tab
integer i, j
integer, dimension(3), parameter :: s = (/ 2,3,4 /)
set = dataSet("test.dat",CREATE)
tab = addTable(set,"some table",100)
col = addColumn(tab,"bool",BOOLEAN)
col = addColumn(tab,"int8",INTEGER8,units="cm",comment="int8 column")
col = addColumn(tab,"int16",INTEGER16,units="dm",comment="int16 column")
col = addColumn(tab,"int32",INTEGER32,units="m",comment="in32 column")
col = addColumn(tab,"real32",REAL32,units="Dm",comment="real32 column")
col = addColumn(tab,"real64",REAL64,units="hm",comment="real64 column")
col = addColumn(tab,"string",STRING,comment="string column",dimensions=(/80/))
arr = addArray(set, "array1", INTEGER16, dimensions=s, units="klm" )
arr = addArray(set, "array2", INTEGER32, dimensions=s, units="kla" )
do i = 0, numberOfBlocks( set ) - 1
blk = block( set, i, READ )
if( blockType( blk ).eq.ARRAY_BLOCK ) then
arr = array( set, name( blk ), READ )
call displayUnits( dataComponent( arr ) )
else
tab = table( set, name( blk ) )
do j = 0, numberOfColumns( tab ) - 1
col = column( tab, j, READ )
call displayUnits( dataComponent( col ) )
end do
end if
end do
call release(set)
end program example_datacomponent
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! This example shows how the deleteAttribute inteface is
! used.
subroutine deleteAllAttributes( attrib )
use dal
implicit none
type(AttributableT) attrib
type(AttributeT) att
integer i
do i = 0, numberOfAttributes( attrib ) - 1
att = attribute( attrib, 0 )
write(*,*) "deleting attribute with name ", name( att )
call deleteAttribute( att )
end do
end subroutine deleteAllAttributes
program example_deleteattribute
use dal
implicit none
type(DataSetT) set
type(TableT) tab
type(ArrayT) arr
set = dataSet("test.dat",CREATE)
call setAttribute(set,"sbool1",.false.,"dataset bool comment")
call setAttribute(set,"sbool2",.true.,"dataset bool comment")
call setAttribute(set,"sbool3",.false.,"table bool comment")
call setAttribute(set,"sbool4",.true.,"table bool comment")
tab = addTable(set,"table",10);
call setAttribute(tab,"sbool1",.false.,"table bool comment")
call setAttribute(tab,"sbool2",.true.,"table bool comment")
call setAttribute(tab,"sbool3",.false.,"table bool comment")
call setAttribute(tab,"sbool4",.true.,"table bool comment")
write(*,*) numberOfAttributes( set )
call deleteAllAttributes( attributable( set ) )
write(*,*) numberOfAttributes( set )
write(*,*) numberOfAttributes( tab )
call deleteAllAttributes( attributable( tab ) )
write(*,*) numberOfAttributes( tab )
call release(set)
end program example_deleteattribute
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! This example shows how the deleteBlock interface
! is used.
program example_deleteblock
use dal
implicit none
type(DataSetT) set
type(TableT) tab
type(BlockT) blk
integer i
set = dataSet("test.dat",CREATE)
tab = addTable(set,"table1",10)
tab = addTable(set,"table2",100)
tab = addTable(set,"table3",1000)
write(*,*) numberOfBlocks( set )
call deleteBlock( set, "table2" );
do i=0,numberOfBlocks( set ) - 1
blk = block( set, 0, READ )
write(*,*) "deleting block with name ", name( blk )
call deleteBlock( set, 0 )
end do
write(*,*) numberOfBlocks( set )
call release(set)
end program example_deleteblock
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
program example_addcolumn
use dal
implicit none
type(DataSetT) set
type(TableT) tab
type(ColumnT) col
integer i
set = dataSet("test.dat",CREATE)
tab = addTable(set,"some table",100)
col = addColumn(tab,"bool",BOOLEAN)
col = addColumn(tab,"int8",INTEGER8,units="cm",comment="int8 column")
col = addColumn(tab,"int16",INTEGER16,units="dm",comment="int16 column")
col = addColumn(tab,"int32",INTEGER32,units="m",comment="in32 column")
col = addColumn(tab,"real32",REAL32,units="Dm",comment="real32 column")
col = addColumn(tab,"real64",REAL64,units="hm",comment="real64 column")
col = addColumn(tab,"string",STRING,comment="string column",dimensions=(/80/))
call deleteColumn( tab, "int32" )
call deleteColumn( tab, 3 ) ! "real32"
do i = 0, numberOfColumns( tab ) - 1
write(*,*) name( column( tab, i, READ ) )
end do
call release(set)
end program example_addcolumn
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! This examples show how to use the deleteRows() subroutine.
program example_deleterows
use dal
implicit none
type(DataSetT) set
type(TableT) tab
type(ColumnT) col1, col2
integer(kind=int32), dimension(:), pointer :: i32
real(kind=single), dimension(:), pointer :: r32
integer i, r
set = dataSet("test.dat",CREATE)
tab = addTable(set,"some table",10)
col1 = addColumn(tab,"col1",INTEGER32,units="m",comment="in32 column")
i32 => int32Data(col1)
do i=0,4
i32(i) = 3*i
end do
call release( col1)
col2 = addColumn(tab,"col2",REAL32,units="Dm",comment="real32 column")
r32 => real32Data(col2)
do i=0,4
r32(i) = 0.5*i
end do
call release( col2)
call copyRows( tab, 0, 5, 5 ) ! copy range [0,4] to [5,9]
i32 => int32Data(col1)
r32 => real32Data(col2)
do i = 0, numberOfRows( tab ) - 1
write(*,*) i32(i), r32(i)
end do
call release(col1)
call release(col2)
r = 0
do i = 0, 9
i32 => int32Data(col1)
if( i32(r) .eq. 6 ) then
write(*,*) "deleting row number ", i
call deleteRows( tab, r, 1 )
else
r = r + 1
end if
call release( col1 )
end do
i32 => int32Data(col1)
r32 => real32Data(col2)
do i = 0, numberOfRows( tab ) - 1
write(*,*) i32(i), r32(i)
end do
call release(set)
end program example_deleterows
This subroutine must only be called by Meta Tasks.
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! This example shows how to use the keepDataSet
! subroutine
program example_keepdiscarddataset
use dal
implicit none
type(DataSetT) set
set = dataSet("test.dat",CREATE)
call release(set) ! The dataset will be released from memory
call keepDataSet("test.dat") ! Tell the dataset server not to discard
! the dataset with name "test.dat"
set = dataSet("test.dat",READ)
call release(set) ! The dataset will not be released from memory
set = dataSet("test.dat",READ) ! The dataset is already in memory, so this
! operation has virtually no overhead.
call release(set) ! The dataset will not be released from memory
call discardDataSet("test.dat") ! Tell the dataset server to discard and
! release the dataset with name "test.dat"
end program example_keepdiscarddataset
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! This example demonstrates the dimensions inteferface.
subroutine fillWithData( dataSetName )
use dal
implicit none
character(len=*), intent(in) :: dataSetName
type(DataSetT) set
type(TableT) tab
type(ColumnT) col
integer(kind=INT32), dimension(:,:,:,:,:), pointer :: c
integer, dimension(:), pointer :: s
integer :: i,j,k,l,m,n
! Reopen dataset and fill with data.
set = dataSet( dataSetName, MODIFY )
tab = table( set, "table" )
col = column( tab, "column", MODIFY )
s => dimensions( col )
c => int32Array4Data( col )
n = 0
do m=0,numberOfRows(tab) - 1
do l=0, s(3) - 1
do k=0, s(2) - 1
do j=0, s(1) - 1
do i=0, s(0) - 1
c(i,j,k,l,m) = n
n = n + 1
end do
end do
end do
end do
end do
call release(col)
call release(set)
end subroutine fillWithData
program example_dimensions
use dal
implicit none
type(DataSetT) set
type(TableT) tab
type(ColumnT) col
integer, dimension(4), parameter :: s = (/ 3,4,5,6 /)
! create a set
set = dataSet("test.dat",CREATE)
tab = addTable(set, "table", 100, "table comment" )
col = addColumn( tab, "column", INTEGER32, "km", s, "column comment" )
call release( set )
call fillWithData( "test.dat" )
end program example_dimensions
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! In this example, a dataset is created with one table and one
! array.
! The generic subroutine displayBlock, which operates on the
! BlockT base type. The blockType() function operates on objects
! of type BlockT.
! The example also shows blocks being retrieved from the dataset
! both by name and by number.
subroutine displayBlock( thisBlock )
use dal
implicit none
type(BlockT), intent(in) :: thisBlock
write(*,*) "The block with name ", name( thisBlock )
if( blockType( thisBlock ) .eq. ARRAY_BLOCK ) then
write(*,*) " is an array."
end if
if( blockType( thisBlock ) .eq. TABLE_BLOCK ) then
write(*,*) " is a table."
end if
end subroutine displayBlock
subroutine displayBlocks( thisSet )
use dal
implicit none
type(DataSetT) thisSet
integer i
interface
subroutine displayBlock( blk )
use dal
implicit none
type(BlockT), intent(in) :: blk
end subroutine displayBlock
end interface
call foreachblock( thisSet, displayBlock )
end subroutine displayBlocks
program example_foreachblock
use dal
implicit none
type(DataSetT) set
type(TableT) tab
type(ArrayT) arr
integer, dimension(3), parameter :: s = (/ 3,4,2 /)
set = dataSet("test.dat",CREATE)
tab = addTable(set,"table",10);
arr = addArray(set, "array", INTEGER32, dimensions=s )
call displayBlock( block( tab ) )
call displayBlock( block( arr ) )
call displayBlock( block( set, "table", READ ) )
call displayBlock( block( set, "array", READ ) )
call displayBlocks( set )
call release(set)
end program example_foreachblock
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! This examples show how the forEachColumn() function is used.
! The column by name is used to get a column and rename it.
! The column by number is used to iterate over all
! columns in the table to output the name, type and units.
subroutine displayColumn( col )
use dal
implicit none
type(ColumnT), intent(in) :: col
write(*,*) name( col ), columnDataType( col ), units( col )
end subroutine displayColumn
program example_foreachcolumn
use dal
implicit none
type(DataSetT) set
type(TableT) tab
type(ColumnT) col
integer i
interface
subroutine displayColumn( col )
use dal
implicit none
type(ColumnT), intent(in) :: col
end subroutine displayColumn
end interface
set = dataSet("test.dat",CREATE)
tab = addTable(set,"some table",100)
col = addColumn(tab,"col1",INTEGER32,units="m1",comment="in32 column")
col = addColumn(tab,"col2",INTEGER32,units="m2",comment="in32 column")
col = addColumn(tab,"col3",INTEGER32,units="m3",comment="in32 column")
col = column( tab, "col2", MODIFY )
call rename( col, "col4" )
call forEachColumn( tab, displayColumn )
call release(set)
end program example_foreachcolumn
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! This example shows how the forEachSubTable() function
! is used.
! This subroutine will fill the subtable with dummy data.
subroutine fill(tab)
use dal
type(TableT), intent(in) :: tab
type(ColumnT) :: xCol, yCol, tCol
real(kind=SINGLE), dimension(:), pointer :: x,y,t
write(*,*) from( tab ), count( tab )
xCol = column(tab,"x",MODIFY)
yCol = column(tab,"y",MODIFY)
tCol = column(tab,"t",MODIFY)
x => real32Data(xCol)
x = 1.23
write(*,*) x
y => real32Data(yCol)
y = 2.34
write(*,*) y
t => real32Data(tCol)
t = 3.45
write(*,*) t
end subroutine fill
! This subroutine will write the contents of the subtable to standard output.
subroutine check(tab)
use dal
type(TableT), intent(in) :: tab
type(ColumnT) :: xCol, yCol, tCol
real(kind=single), dimension(:), pointer :: x,y,t
write(*,*) from( tab ), count( tab )
xCol = column(tab,"x",READ)
yCol = column(tab,"y",READ)
tCol = column(tab,"t",READ)
x => real32Data(xCol)
y => real32Data(yCol)
t => real32Data(tCol)
write(*,*) "DATA:", x, y, t
end subroutine check
program example_foreachsubtable
use dal
implicit none
! This part of the program will apply reportX to a table.
type(DataSetT) :: set
type(TableT) :: tab
type(ColumnT) :: xCol, yCol, tCol
real(kind=SINGLE), dimension(:), pointer :: x,y,t
interface
subroutine fill( subtab )
use dal
implicit none
type(TableT), intent(in) :: subtab
end subroutine fill
subroutine check( subtab )
use dal
implicit none
type(TableT), intent(in) :: subtab
end subroutine check
end interface
set = dataSet("test.dat",CREATE)
tab = addTable(set,"events",10)
xCol = addColumn(tab,"x",real32,"mm")
yCol = addColumn(tab,"y",real32,"mm")
tCol = addColumn(tab,"t",real32,"s")
call forEachSubTable(tab,fill)
call forEachSubTable(tab,check)
call release(set)
end program example_foreachsubtable
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! This example shows how the forEachSubTable() function
! is used.
! This subroutine will fill the subtable with dummy data.
subroutine fill(tab)
use dal
type(TableT), intent(in) :: tab
type(ColumnT) :: xCol, yCol, tCol
real(kind=SINGLE), dimension(:), pointer :: x,y,t
xCol = column(tab,"x",MODIFY)
yCol = column(tab,"y",MODIFY)
tCol = column(tab,"t",MODIFY)
x => real32Data(xCol)
x = 1.23
y => real32Data(yCol)
y = 2.34
t => real32Data(tCol)
t = 0
end subroutine fill
! This subroutine will write the contents of the subtable to standard output.
subroutine check(tab)
use dal
type(TableT), intent(in) :: tab
type(ColumnT) :: xCol, yCol, tCol
real(kind=single), dimension(:), pointer :: x,y,t
xCol = column(tab,"x",READ)
yCol = column(tab,"y",READ)
tCol = column(tab,"t",READ)
x => real32Data(xCol)
y => real32Data(yCol)
t => real32Data(tCol)
write(*,*) x, y, t
end subroutine check
program example_foreachsubtable
use dal
implicit none
! This part of the program will apply reportX to a table.
type(DataSetT) :: set
type(TableT) :: tab
type(ColumnT) :: xCol, yCol, tCol
real(kind=SINGLE), dimension(:), pointer :: x,y,t
interface
subroutine fill( subtab )
use dal
implicit none
type(TableT), intent(in) :: subtab
end subroutine fill
subroutine check( subtab )
use dal
implicit none
type(TableT), intent(in) :: subtab
end subroutine check
end interface
set = dataSet("test.dat",CREATE)
tab = addTable(set,"events",10)
xCol = addColumn(tab,"x",real32,"mm")
yCol = addColumn(tab,"y",real32,"mm")
tCol = addColumn(tab,"t",real32,"s")
call forEachRow(tab,fill)
call forEachRow(tab,check)
call release(set)
end program example_foreachsubtable
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! This example shows how the seek functions
! are used.
! This subroutine will dispaly the seek values of the given table and column.
subroutine whatisseek(tab)
use dal
type(TableT), intent(in) :: tab
type(ColumnT) :: col
write(*,*) from( tab ), count( tab )
col = column(tab,"x",MODIFY)
write(*,*) from( col ), count( col )
end subroutine whatisseek
program example_seek
use dal
implicit none
type(DataSetT) :: set
type(TableT) :: tab
type(ColumnT) :: col
interface
subroutine whatisseek( subtab )
use dal
implicit none
type(TableT), intent(in) :: subtab
end subroutine whatisseek
end interface
set = dataSet("test.dat",CREATE)
tab = addTable(set,"events",10)
col = addColumn(tab,"x",real32,"mm")
call forEachSubTable(tab,whatisseek)
call release(set)
end program example_seek
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! This example shoes how the hasAttribute interface is used.
program example_hasattribute
use dal
implicit none
type(DataSetT) set
type(AttributeT) att
set = dataSet("test.dat",CREATE)
call setAttribute(set,"sbool1",.false.,"dataset bool comment")
if( hasAttribute( set, "sbool2" ) ) then
write(*,*) 'That is not possible'
end if
if( hasAttribute( set, "sbool1" ) ) then
att = attribute( set, "sbool1" )
write(*,*) name( att ), " = ", booleanAttribute( att )
end if
call release(set)
end program example_hasattribute
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! This example showas how the hasBlock() function is used.
! In the example, a dataset is created with one table and one
! array.
! The generic subroutine displayBlock, which operates on the
! BlockT base type. The blockType() function operates on objects
! of type BlockT.
! The dataset is testes for the existence of the table and the array, and in
! each case, the block is displayed.
subroutine displayBlock( thisBlock )
use dal
implicit none
type(BlockT) thisBlock
write(*,*) "The block with name ", name( thisBlock )
if( blockType( thisBlock ) .eq. ARRAY_BLOCK ) then
write(*,*) " is an array."
end if
if( blockType( thisBlock ) .eq. TABLE_BLOCK ) then
write(*,*) " is a table."
end if
end subroutine displayBlock
program example_hasblock
use dal
implicit none
type(DataSetT) set
type(TableT) tab
type(ArrayT) arr
integer, dimension(3), parameter :: s = (/ 3,4,2 /)
set = dataSet("test.dat",CREATE)
tab = addTable(set,"table",10);
arr = addArray(set, "array", INTEGER32, dimensions=s )
call release(set)
set = dataSet("test.dat",READ)
if( hasBlock( set, "table" ) ) then
call displayBlock( block( set, "table",READ ) )
end if
if( hasBlock( set, "array" ) ) then
call displayBlock( block( set, "array",READ ) )
end if
call release(set)
end program example_hasblock
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! This examples show how the hasColumn() function is used.
! The column by name is used to get a column and rename it.
! The column by number is used to iterate over all
! columns in the table to output the name, type and units.
program example_hascolumn
use dal
implicit none
type(DataSetT) set
type(TableT) tab
type(ColumnT) col
integer i
set = dataSet("test.dat",CREATE)
tab = addTable(set,"some table",100)
col = addColumn(tab,"col1",INTEGER32,units="m1",comment="in32 column")
col = addColumn(tab,"col2",INTEGER32,units="m2",comment="in32 column")
col = addColumn(tab,"col3",INTEGER32,units="m3",comment="in32 column")
col = column( tab, "col2", MODIFY )
call rename( col, "col4" )
if( hasColumn( tab, "col2" ) ) then
write(*,*) 'This is not possible, since col4 was renamed to col4'
end if
do i =0, numberOfColumns( tab ) - 1
col = column( tab, i, READ )
write(*,*) name( col ), columnDataType( col ), units( col )
end do
call release(set)
end program example_hascolumn
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! This example shows how null values are used.
subroutine check( thisNullable )
use dal
type(NullableT), intent(in) :: thisNullable
write(*,*) "Null defined?: ", nullDefined( thisNullable ), nullType( thisNullable )
end subroutine check
program example_nullvalues
use dal
use errorhandling
implicit none
type(DataSetT) set
type(ArrayT) arr1, arr2
type(TableT) tab
type(ColumnT) col1, col2
integer(kind=int32), dimension(:), pointer :: i32
real(kind=double), dimension(:), pointer :: r64
integer(kind=int32), dimension(:,:,:), pointer :: a1, a2
integer, dimension(3), parameter :: s = (/ 3,4,2 /)
integer :: i,j,k,n
! create a set
set = dataSet("test.dat",CREATE)
arr1 = addArray(set, "array1", INTEGER32, dimensions=s )
arr2 = addArray(set, "array2", arrayDataType( arr1 ), dimensions=s )
! fill with unique numbers
a1 => int32Array3Data(arr1)
a2 => int32Array3Data(arr1)
n = 0
do k=0,1
do j=0,3
do i=0,2
a1(i,j,k) = n
a2(i,j,k) = a1(i,j,k) + 1
n = n + 1
end do
end do
end do
call setNullValue( arr1, 999999 )
call check( nullable( arr1 ) )
call setToNull( arr1, 0 ) ! Set the first element of array arr1 to null.
! Would have given an error, if the null
! value of array arr1 had not been set.
if( nullType( arr1 ) .eq. INTEGER_NULL ) then !
write(*,*) "Using null value of arr1, in arr2"
call setNullValue( arr2, intNullValue( arr1 ))
else
call setNullValue( arr2, 999999 )
end if
call check( nullable( arr2 ) )
call setToNull( arr2, 1 ) ! Set the second element of array arr2 to null.
! Would have given an error, if the null
! value of array arr2 had not been set.
call release(arr1)
call release(arr2)
tab = addTable(set,"some table",100)
col1 = addColumn(tab,"int32",INTEGER32,units="m",comment="in32 column")
i32 => int32Data(col1)
do i=0,numberOfRows(tab)-1
i32(i) = 3*i
end do
call setNullValue( col1, 999999 )
call check( nullable( col1 ) )
call setToNull( col1, 0 ) ! Set the first element of column col1 to null.
col2 = addColumn(tab,"real64",REAL64,units="hm",comment="real64 column")
r64 => real64Data(col2)
do i=0,numberOfRows(tab)-1
r64(i) = 0.25*i
end do
! col is a non-integer column and it would be an
! an error to call setNullValue().
call check( nullable( col2 ) )
call setToNull( col2, 0 ) ! Set the first element of column col2 to null.
if( hasNulls( col2 ) ) then
do i=0,numberOfRows(tab)-1
if( isNull( col2, i ) ) then
write(*,*) "element", i, "is null"
else
write(*,*) "element", i, "is", r64(i)
endif
end do
endif
call release(col1)
call release(col2)
call release(set)
end program example_nullvalues
! ESA (C) 2000-2018 ! ! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS). ! ! SAS is free software: you can redistribute it and/or modify ! it under the terms of the GNU General Public License as published by ! the Free Software Foundation, either version 3 of the License, or ! (at your option) any later version. ! ! SAS is distributed in the hope that it will be useful, ! but WITHOUT ANY WARRANTY; without even the implied warranty of ! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the ! GNU General Public License for more details. ! ! You should have received a copy of the GNU General Public License ! along with SAS. If not, see <http://www.gnu.org/licenses/>. ! This examp,e shows how to open a dataset ! with a specific memory model. program example_memorymodel use dal implicit none type(DataSetT) set set = dataSet( "test.dat",CREATE,HIGH_MEMORY ) call release( set ) set = dataSet( "test.dat",HIGH_LOW_MEMORY ) call release( set ) end program example_memorymodel
! ESA (C) 2000-2018 ! ! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS). ! ! SAS is free software: you can redistribute it and/or modify ! it under the terms of the GNU General Public License as published by ! the Free Software Foundation, either version 3 of the License, or ! (at your option) any later version. ! ! SAS is distributed in the hope that it will be useful, ! but WITHOUT ANY WARRANTY; without even the implied warranty of ! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the ! GNU General Public License for more details. ! ! You should have received a copy of the GNU General Public License ! along with SAS. If not, see <http://www.gnu.org/licenses/>. ! This examp,e shows how to open a dataset ! with a specific memory model. program example_memorymodel use dal implicit none type(DataSetT) set set = dataSet( "test.dat",CREATE,HIGH_MEMORY ) call release( set ) set = dataSet( "test.dat",HIGH_LOW_MEMORY ) call release( set ) end program example_memorymodel
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! This examples show how to use the insertRows() subroutine.
program example_insertrows
use dal
implicit none
type(DataSetT) set
type(TableT) tab
type(ColumnT) col1, col2
integer(kind=int32), dimension(:), pointer :: i32
real(kind=single), dimension(:), pointer :: r32
integer i, r
set = dataSet("test.dat",CREATE)
tab = addTable(set,"some table",5)
col1 = addColumn(tab,"col1",INTEGER32,units="m",comment="in32 column")
i32 => int32Data(col1)
do i=0,4
i32(i) = 3*i
end do
call release( col1)
col2 = addColumn(tab,"col2",REAL32,units="Dm",comment="real32 column")
r32 => real32Data(col2)
do i=0,4
r32(i) = 0.5*i
end do
call release( col2)
! insert 5 additional rows, at the end of the table
call insertRows( tab, 5, 5 )
! copy the first 5 rows to the new rows.
call copyRows( tab, 0, 5, 5 ) ! copy range [0,4] to [5,9]
i32 => int32Data(col1)
r32 => real32Data(col2)
do i = 0, numberOfRows( tab ) - 1
write(*,*) i32(i), r32(i)
end do
call release(col1)
call release(col2)
r = 0
do i = 0, 9
i32 => int32Data(col1)
if( i32(r) .eq. 6 ) then
write(*,*) "deleting row number ", i
call deleteRows( tab, r, 1 )
else
r = r + 1
end if
call release( col1 )
end do
i32 => int32Data(col1)
r32 => real32Data(col2)
do i = 0, numberOfRows( tab ) - 1
write(*,*) i32(i), r32(i)
end do
call release(set)
end program example_insertrows
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! This example shows how to use the int8Array2Data interface.
! In the example a dataset is created (opened) containing
! a table with 2 columns of two 2-dimensional arrays.
!
! The second array has the same data type as the first; this
! is ensured by using the arrayDataType() function to determine
! the data type of the first array.
!
! The columns are then initialised, on a row-by-row
! basis (i.e. accessing the column's data cell-by-cell),
! before the dataset is released (closed).
program example_cellarray2data
use dal
use errorhandling
implicit none
type(DataSetT) set
type(TableT) tab
type(ColumnT) col1, col2
integer(kind=INT8), dimension(:,:), pointer :: c1, c2
integer, dimension(2), parameter :: s = (/ 3,4 /)
integer :: i,j,k,n
! create a set
set = dataSet("test.dat",CREATE)
tab = addTable(set, "table", 100, "table comment" )
col1 = addColumn( tab, "column1", INTEGER8, "km", s, "column comment" )
col2 = addColumn( tab, "column2", columnDataType( col1 ), "km", s, "column comment" )
! fill with unique numbers
n = 0
do k=0,numberOfRows(tab) - 1
c1 => int8Array2Data(col1,k)
c2 => int8Array2Data(col2,k)
do j=0,3
do i=0,2
c1(i,j) = n
c2(i,j) = c1(i,j)
n = n + 1
end do
end do
end do
call release(col1)
call release(col2)
call release(set)
end program example_cellarray2data
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! This example shows how to use the int8Array2Data interface.
! In the example a dataset is created (opened) containing
! a table with 2 2-dimensional arrays.
!
! The second array has the same data type as the first; this
! is ensured by using the arrayDataType() function to determine
! the data type of the first array.
!
! The columns are then initialised, on a row-by-row
! basis (i.e. accessing the column's data cell-by-cell),
! before the dataset is released (closed).
program example_arrayarray2data
use dal
use errorhandling
implicit none
type(DataSetT) set
type(TableT) tab
type(ArrayT) arr1, arr2
integer(kind=INT8), dimension(:,:), pointer :: a1, a2
integer, dimension(2), parameter :: s = (/ 3,4 /)
integer :: i,j,n
! create a set
set = dataSet("test.dat",CREATE)
arr1 = addArray( set, "array1", INTEGER8, s, "km", "array comment" )
arr2 = addArray( set, "array2", INTEGER8, s, "km", "array comment" )
! fill with unique numbers
n = 0
a1 => int8Array2Data(arr1)
a2 => int8Array2Data(arr2)
do j=0,3
do i=0,2
a1(i,j) = n
a2(i,j) = a1(i,j)
n = n + 1
end do
end do
call release(arr1)
call release(arr2)
call release(set)
end program example_arrayarray2data
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! In this example add dataset is created (opened) containing
! a table with 2 columns of two 2-dimensional arrays.
!
! The second array has the same data type as the first; this
! is ensured by using the arrayDataType() function to determine
! the data type of the first array.
!
! The columns are then initialised before the
! dataset is released (closed).
program example_array2data
use dal
use errorhandling
implicit none
type(DataSetT) set
type(TableT) tab
type(ColumnT) col1, col2
integer(kind=INT8), dimension(:,:,:), pointer :: c1, c2
integer, dimension(2), parameter :: s = (/ 3,4 /)
integer :: i,j,k,n
! create a set
set = dataSet("test.dat",CREATE)
tab = addTable(set, "table", 100, "table comment" )
col1 = addColumn( tab, "column1", INTEGER8, "km", s, "column comment" )
col2 = addColumn( tab, "column2", columnDataType( col1 ), "km", s, "column comment" )
! fill with unique numbers
c1 => int8Array2Data(col1)
c2 => int8Array2Data(col2)
n = 0
do k=0,numberOfRows(tab) - 1
do j=0,3
do i=0,2
c1(i,j,k) = n
c2(i,j,k) = c1(i,j,k)
n = n + 1
end do
end do
end do
call release(col1)
call release(col2)
call release(set)
end program example_array2data
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! In this example add dataset is created (opened) containing
! a table with 2 columns of two 3-dimensional arrays.
!
! The second array has the same data type as the first; this
! is ensured by using the arrayDataType() function to determine
! the data type of the first array.
!
! The columns are then initialised, on a row-by-row
! basis (i.e. accessing the column's data cell-by-cell),
! before the dataset is released (closed).
program example_cellarray3data
use dal
use errorhandling
implicit none
type(DataSetT) set
type(TableT) tab
type(ColumnT) col1, col2
integer(kind=INT8), dimension(:,:,:), pointer :: c1, c2
integer, dimension(3), parameter :: s = (/ 3,4,5 /)
integer :: i,j,k,l,n
! create a set
set = dataSet("test.dat",CREATE)
tab = addTable(set, "table", 100, "table comment" )
col1 = addColumn( tab, "column1", INTEGER8, "km", s, "column comment" )
col2 = addColumn( tab, "column2", columnDataType( col1 ), "km", s, "column comment" )
! fill with unique numbers
n = 0
do l=0,numberOfRows(tab) - 1
c1 => int8Array3Data(col1,l)
c2 => int8Array3Data(col2,l)
do k=0,4
do j=0,3
do i=0,2
c1(i,j,k) = n
c2(i,j,k) = c1(i,j,k)
n = n + 1
end do
end do
end do
end do
call release(col1)
call release(col2)
call release(set)
end program example_cellarray3data
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! This example shows how to use the int8Array2Data interface.
! In the example a dataset is created (opened) containing
! a table with 2 3-dimensional arrays.
!
! The second array has the same data type as the first; this
! is ensured by using the arrayDataType() function to determine
! the data type of the first array.
!
! The columns are then initialised, on a row-by-row
! basis (i.e. accessing the column's data cell-by-cell),
! before the dataset is released (closed).
program example_arrayarray3data
use dal
use errorhandling
implicit none
type(DataSetT) set
type(TableT) tab
type(ArrayT) arr1, arr2
integer(kind=INT8), dimension(:,:,:), pointer :: a1, a2
integer, dimension(3), parameter :: s = (/ 3,4,5 /)
integer :: i,j,k,n
! create a set
set = dataSet("test.dat",CREATE)
arr1 = addArray( set, "array1", INTEGER8, s, "km", "array comment" )
arr2 = addArray( set, "array2", INTEGER8, s, "km", "array comment" )
! fill with unique numbers
n = 0
a1 => int8Array3Data(arr1)
a2 => int8Array3Data(arr2)
do k=0,4
do j=0,3
do i=0,2
a1(i,j,k) = n
a2(i,j,k) = a1(i,j,k)
n = n + 1
end do
end do
end do
call release(arr1)
call release(arr2)
call release(set)
end program example_arrayarray3data
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! In this example add dataset is created (opened) containing
! a table with 2 columns of two 3-dimensional arrays.
!
! The second array has the same data type as the first; this
! is ensured by using the arrayDataType() function to determine
! the data type of the first array.
!
! The columns are then initialised before the
! dataset is released (closed).
program example_array3data
use dal
use errorhandling
implicit none
type(DataSetT) set
type(TableT) tab
type(ColumnT) col1, col2
integer(kind=INT8), dimension(:,:,:,:), pointer :: c1, c2
integer, dimension(3), parameter :: s = (/ 3,4,5 /)
integer :: i,j,k,l,n
! create a set
set = dataSet("test.dat",CREATE)
tab = addTable(set, "table", 100, "table comment" )
col1 = addColumn( tab, "column1", INTEGER8, "km", s, "column comment" )
col2 = addColumn( tab, "column2", columnDataType( col1 ), "km", s, "column comment" )
! fill with unique numbers
c1 => int8Array3Data(col1)
c2 => int8Array3Data(col1)
n = 0
do l=0,numberOfRows(tab) - 1
do k = 0,4
do j=0,3
do i=0,2
c1(i,j,k,l) = n
c2(i,j,k,l) = c1(i,j,k,l)
n = n + 1
end do
end do
end do
end do
call release(col1)
call release(col2)
call release(set)
end program example_array3data
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! In this example add dataset is created (opened) containing
! a table with 2 columns of two 4-dimensional arrays.
!
! The second array has the same data type as the first; this
! is ensured by using the arrayDataType() function to determine
! the data type of the first array.
!
! The columns are then initialised, on a row-by-row
! basis (i.e. accessing the column's data cell-by-cell),
! before the dataset is released (closed).
program example_cellarray4data
use dal
use errorhandling
implicit none
type(DataSetT) set
type(TableT) tab
type(ColumnT) col1, col2
integer(kind=INT8), dimension(:,:,:,:), pointer :: c1, c2
integer, dimension(4), parameter :: s = (/ 3,4,5,6 /)
integer :: i,j,k,l,m,n
! create a set
set = dataSet("test.dat",CREATE)
tab = addTable(set, "table", 100, "table comment" )
col1 = addColumn( tab, "column1", INTEGER8, "km", s, "column comment" )
col2 = addColumn( tab, "column2", columnDataType( col1 ), "km", s, "column comment" )
! fill with unique numbers
n = 0
do m=0,numberOfRows(tab) - 1
c1 => int8Array4Data(col1,m)
c2 => int8Array4Data(col2,m)
do l=0,5
do k=0,4
do j=0,3
do i=0,2
c1(i,j,k,l) = n
c2(i,j,k,l) = c1(i,j,k,l)
n = n + 1
end do
end do
end do
end do
end do
call release(col1)
call release(col2)
call release(set)
end program example_cellarray4data
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! In this example add dataset is created (opened) containing
! a table with 2 columns of two 4-dimensional arrays.
!
! The second array has the same data type as the first; this
! is ensured by using the arrayDataType() function to determine
! the data type of the first array.
!
! The columns are then initialised before the
! dataset is released (closed).
program example_array4data
use dal
use errorhandling
implicit none
type(DataSetT) set
type(TableT) tab
type(ColumnT) col1, col2
integer(kind=INT8), dimension(:,:,:,:,:), pointer :: c1, c2
integer, dimension(4), parameter :: s = (/ 3,4,5,6 /)
integer :: i,j,k,l,m,n
! create a set
set = dataSet("test.dat",CREATE)
tab = addTable(set, "table", 100, "table comment" )
col1 = addColumn( tab, "column1", INTEGER8, "km", s, "column comment" )
col2 = addColumn( tab, "column2", columnDataType( col1 ), "km", s, "column comment" )
! fill with unique numbers
c1 => int8Array4Data(col1)
c2 => int8Array4Data(col1)
n = 0
do m=0,numberOfRows(tab) - 1
do l=0,5
do k=0,4
do j=0,3
do i=0,2
c1(i,j,k,l,m) = n
c2(i,j,k,l,m) = c1(i,j,k,l,m)
n = n + 1
end do
end do
end do
end do
end do
call release(col1)
call release(col2)
call release(set)
end program example_array4data
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! This example shows how int8 attributes are used.
! The program creates a dataset containing two int8 attributes,
! together with a table containing two int8 attributes.
! The attributes are then accessed, by name, with
! the int8Attribute() function.
! Also, it is shown how to access the attributes by position.
program example_int8attribute
use dal
use errorhandling
implicit none
type(DataSetT) set
type(TableT) tab
type(AttributeT) att
integer i
set = dataSet("test.dat",CREATE)
call setAttribute(set,"int1",1,"int comment")
call setAttribute(set,"int2",2,"int comment")
tab = addTable(set,"table",10);
call setAttribute(tab,"int1",3,"int comment")
call setAttribute(tab,"int2",4,"int comment")
write(*,*) int8Attribute( set, "int1" ) ! output '1'
write(*,*) int8Attribute( set, "int2" ) ! output '2'
write(*,*) int8Attribute( tab, "int1" ) ! output '3'
write(*,*) int8Attribute( tab, "int2" ) ! output '4'
do i = 0, numberOfAttributes( set ) - 1
att = attribute( set, i )
write(*,*) int8Attribute( att ) ! output the sequence 1, 2
end do
call release(set)
end program example_int8attribute
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! In this example add dataset is created (opened) containing
! a table with 2 columns of two 4-dimensional arrays.
!
! The second array has the same data type as the first; this
! is ensured by using the arrayDataType() function to determine
! the data type of the first array.
!
! The columns are then initialised, and then the second column
! is output by accessing the column's data as a flat vector.
program example_int8data
use dal
use errorhandling
implicit none
type(DataSetT) set
type(TableT) tab
type(ColumnT) col1, col2
integer(kind=INT8), dimension(:,:,:,:,:), pointer :: c1, c2
integer(kind=INT8), dimension(:), pointer :: cd
integer, dimension(4), parameter :: s = (/ 3,4,5,6 /)
integer :: i,j,k,l,m,n
! create a set
set = dataSet("test.dat",CREATE)
tab = addTable(set, "table", 5, "table comment" )
col1 = addColumn( tab, "column1", INTEGER8, "km", s, "column comment" )
col2 = addColumn( tab, "column2", columnDataType( col1 ), "km", s, "column comment" )
! fill with unique numbers
c1 => int8Array4Data(col1)
c2 => int8Array4Data(col2)
n = 0
do m=0,numberOfRows(tab) - 1
do l=0,5
do k=0,4
do j=0,3
do i=0,2
c1(i,j,k,l,m) = n
c2(i,j,k,l,m) = c1(i,j,k,l,m)
n = n + 1
end do
end do
end do
end do
end do
call release(col1)
call release(col2)
! Output the col2
cd => int8Data( col2 ) ! Access the column's 4-dimensional data as a flat vector.
do n = 0,numberOfElements(col1) * numberOfRows(tab) - 1
write(*,*) cd(n)
end do
call release(col2)
call release(set)
end program example_int8data
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! In this example add dataset is created (opened) containing
! a table with 2 columns of two vector arrays.
!
! The second array has the same data type as the first; this
! is ensured by using the arrayDataType() function to determine
! the data type of the first array.
!
! The columns are then initialised, on a row-by-row
! basis (i.e. accessing the column's data cell-by-cell),
! before the dataset is released (closed).
program example_cellvectordata
use dal
use errorhandling
implicit none
type(DataSetT) set
type(TableT) tab
type(ColumnT) col1, col2
integer(kind=INT8), dimension(:), pointer :: c1, c2
integer, dimension(1), parameter :: s = (/ 3 /)
integer :: i,m,n
! create a set
set = dataSet("test.dat",CREATE)
tab = addTable(set, "table", 100, "table comment" )
col1 = addColumn( tab, "column1", INTEGER8, "km", s, "column comment" )
col2 = addColumn( tab, "column2", columnDataType( col1 ), "km", s, "column comment" )
! fill with unique numbers
n = 0
do m=0,numberOfRows(tab) - 1
c1 => int8VectorData(col1,m)
c2 => int8VectorData(col2,m)
do i=0,2
c1(i) = n
c2(i) = c1(i)
n = n + 1
end do
end do
call release(col1)
call release(col2)
call release(set)
end program example_cellvectordata
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! This example shows how to use the int8Array2Data interface.
! In the example a dataset is created (opened) containing
! a table with 2 vector arrays.
!
! The second array has the same data type as the first; this
! is ensured by using the arrayDataType() function to determine
! the data type of the first array.
!
! The array is then initialised,
program example_arrayvectordata
use dal
use errorhandling
implicit none
type(DataSetT) set
type(TableT) tab
type(ArrayT) arr1, arr2
integer(kind=INT8), dimension(:), pointer :: a1, a2
integer, dimension(1), parameter :: s = (/ 3 /)
integer :: i,n
! create a set
set = dataSet("test.dat",CREATE)
arr1 = addArray( set, "array1", INTEGER8, s, "km", "array comment" )
arr2 = addArray( set, "array2", INTEGER8, s, "km", "array comment" )
! fill with unique numbers
n = 0
a1 => int8VectorData(arr1)
a2 => int8VectorData(arr2)
do i=0,2
a1(i) = n
a2(i) = a1(i)
n = n + 1
end do
call release(arr1)
call release(arr2)
call release(set)
end program example_arrayvectordata
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! In this example add dataset is created (opened) containing
! a table with 2 columns of two vector arrays.
!
! The second column has the same data type as the first; this
! is ensured by using the columnDataType() function to determine
! the data type of the first array.
!
! The columns are then initialised before the
! dataset is released (closed).
program example_columnvectordata
use dal
use errorhandling
implicit none
type(DataSetT) set
type(TableT) tab
type(ColumnT) col1, col2
integer(kind=INT8), dimension(:,:), pointer :: c1, c2
integer, dimension(1), parameter :: s = (/ 3 /)
integer :: i,m,n
! create a set
set = dataSet("test.dat",CREATE)
tab = addTable(set, "table", 10, "table comment" )
col1 = addColumn( tab, "column1", INTEGER8, "km", s, "column comment" )
col2 = addColumn( tab, "column2", columnDataType( col1 ), "km", s, "column comment" )
! fill with unique numbers
c1 => int8VectorData(col1)
c2 => int8VectorData(col2)
n = 0
do m=0,numberOfRows(tab) - 1
do i=0,2
c1(i,m) = n
c2(i,m) = c1(i,m)
n = n + 1
end do
end do
call release(col1)
call release(col2)
call release(set)
end program example_columnvectordata
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! This example shows how to use the int16Array2Data interface.
! In the example a dataset is created (opened) containing
! a table with 2 columns of two 2-dimensional arrays.
!
! The second array has the same data type as the first; this
! is ensured by using the arrayDataType() function to determine
! the data type of the first array.
!
! The columns are then initialised, on a row-by-row
! basis (i.e. accessing the column's data cell-by-cell),
! before the dataset is released (closed).
program example_cellarray2data
use dal
use errorhandling
implicit none
type(DataSetT) set
type(TableT) tab
type(ColumnT) col1, col2
integer(kind=INT16), dimension(:,:), pointer :: c1, c2
integer, dimension(2), parameter :: s = (/ 3,4 /)
integer :: i,j,k,n
! create a set
set = dataSet("test.dat",CREATE)
tab = addTable(set, "table", 100, "table comment" )
col1 = addColumn( tab, "column1", INTEGER16, "km", s, "column comment" )
col2 = addColumn( tab, "column2", columnDataType( col1 ), "km", s, "column comment" )
! fill with unique numbers
n = 0
do k=0,numberOfRows(tab) - 1
c1 => int16Array2Data(col1,k)
c2 => int16Array2Data(col2,k)
do j=0,3
do i=0,2
c1(i,j) = n
c2(i,j) = c1(i,j)
n = n + 1
end do
end do
end do
call release(col1)
call release(col2)
call release(set)
end program example_cellarray2data
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! This example shows how to use the int16Array2Data interface.
! In the example a dataset is created (opened) containing
! a table with 2 2-dimensional arrays.
!
! The second array has the same data type as the first; this
! is ensured by using the arrayDataType() function to determine
! the data type of the first array.
!
! The columns are then initialised, on a row-by-row
! basis (i.e. accessing the column's data cell-by-cell),
! before the dataset is released (closed).
program example_arrayarray2data
use dal
use errorhandling
implicit none
type(DataSetT) set
type(TableT) tab
type(ArrayT) arr1, arr2
integer(kind=INT16), dimension(:,:), pointer :: a1, a2
integer, dimension(2), parameter :: s = (/ 3,4 /)
integer :: i,j,n
! create a set
set = dataSet("test.dat",CREATE)
arr1 = addArray( set, "array1", INTEGER16, s, "km", "array comment" )
arr2 = addArray( set, "array2", INTEGER16, s, "km", "array comment" )
! fill with unique numbers
n = 0
a1 => int16Array2Data(arr1)
a2 => int16Array2Data(arr2)
do j=0,3
do i=0,2
a1(i,j) = n
a2(i,j) = a1(i,j)
n = n + 1
end do
end do
call release(arr1)
call release(arr2)
call release(set)
end program example_arrayarray2data
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! In this example add dataset is created (opened) containing
! a table with 2 columns of two 2-dimensional arrays.
!
! The second array has the same data type as the first; this
! is ensured by using the arrayDataType() function to determine
! the data type of the first array.
!
! The columns are then initialised before the
! dataset is released (closed).
program example_array2data
use dal
use errorhandling
implicit none
type(DataSetT) set
type(TableT) tab
type(ColumnT) col1, col2
integer(kind=INT16), dimension(:,:,:), pointer :: c1, c2
integer, dimension(2), parameter :: s = (/ 3,4 /)
integer :: i,j,k,n
! create a set
set = dataSet("test.dat",CREATE)
tab = addTable(set, "table", 100, "table comment" )
col1 = addColumn( tab, "column1", INTEGER16, "km", s, "column comment" )
col2 = addColumn( tab, "column2", columnDataType( col1 ), "km", s, "column comment" )
! fill with unique numbers
c1 => int16Array2Data(col1)
c2 => int16Array2Data(col2)
n = 0
do k=0,numberOfRows(tab) - 1
do j=0,3
do i=0,2
c1(i,j,k) = n
c2(i,j,k) = c1(i,j,k)
n = n + 1
end do
end do
end do
call release(col1)
call release(col2)
call release(set)
end program example_array2data
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! In this example add dataset is created (opened) containing
! a table with 2 columns of two 3-dimensional arrays.
!
! The second array has the same data type as the first; this
! is ensured by using the arrayDataType() function to determine
! the data type of the first array.
!
! The columns are then initialised, on a row-by-row
! basis (i.e. accessing the column's data cell-by-cell),
! before the dataset is released (closed).
program example_cellarray3data
use dal
use errorhandling
implicit none
type(DataSetT) set
type(TableT) tab
type(ColumnT) col1, col2
integer(kind=INT16), dimension(:,:,:), pointer :: c1, c2
integer, dimension(3), parameter :: s = (/ 3,4,5 /)
integer :: i,j,k,l,n
! create a set
set = dataSet("test.dat",CREATE)
tab = addTable(set, "table", 100, "table comment" )
col1 = addColumn( tab, "column1", INTEGER16, "km", s, "column comment" )
col2 = addColumn( tab, "column2", columnDataType( col1 ), "km", s, "column comment" )
! fill with unique numbers
n = 0
do l=0,numberOfRows(tab) - 1
c1 => int16Array3Data(col1,l)
c2 => int16Array3Data(col2,l)
do k=0,4
do j=0,3
do i=0,2
c1(i,j,k) = n
c2(i,j,k) = c1(i,j,k)
n = n + 1
end do
end do
end do
end do
call release(col1)
call release(col2)
call release(set)
end program example_cellarray3data
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! This example shows how to use the int8Array2Data interface.
! In the example a dataset is created (opened) containing
! a table with 2 3-dimensional arrays.
!
! The second array has the same data type as the first; this
! is ensured by using the arrayDataType() function to determine
! the data type of the first array.
!
! The columns are then initialised, on a row-by-row
! basis (i.e. accessing the column's data cell-by-cell),
! before the dataset is released (closed).
program example_arrayarray3data
use dal
use errorhandling
implicit none
type(DataSetT) set
type(TableT) tab
type(ArrayT) arr1, arr2
integer(kind=INT16), dimension(:,:,:), pointer :: a1, a2
integer, dimension(3), parameter :: s = (/ 3,4,5 /)
integer :: i,j,k,n
! create a set
set = dataSet("test.dat",CREATE)
arr1 = addArray( set, "array1", INTEGER16, s, "km", "array comment" )
arr2 = addArray( set, "array2", INTEGER16, s, "km", "array comment" )
! fill with unique numbers
n = 0
a1 => int16Array3Data(arr1)
a2 => int16Array3Data(arr2)
do k=0,4
do j=0,3
do i=0,2
a1(i,j,k) = n
a2(i,j,k) = a1(i,j,k)
n = n + 1
end do
end do
end do
call release(arr1)
call release(arr2)
call release(set)
end program example_arrayarray3data
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! In this example add dataset is created (opened) containing
! a table with 2 columns of two 3-dimensional arrays.
!
! The second array has the same data type as the first; this
! is ensured by using the arrayDataType() function to determine
! the data type of the first array.
!
! The columns are then initialised before the
! dataset is released (closed).
program example_array3data
use dal
use errorhandling
implicit none
type(DataSetT) set
type(TableT) tab
type(ColumnT) col1, col2
integer(kind=INT16), dimension(:,:,:,:), pointer :: c1, c2
integer, dimension(3), parameter :: s = (/ 3,4,5 /)
integer :: i,j,k,l,n
! create a set
set = dataSet("test.dat",CREATE)
tab = addTable(set, "table", 100, "table comment" )
col1 = addColumn( tab, "column1", INTEGER16, "km", s, "column comment" )
col2 = addColumn( tab, "column2", columnDataType( col1 ), "km", s, "column comment" )
! fill with unique numbers
c1 => int16Array3Data(col1)
c2 => int16Array3Data(col1)
n = 0
do l=0,numberOfRows(tab) - 1
do k = 0,4
do j=0,3
do i=0,2
c1(i,j,k,l) = n
c2(i,j,k,l) = c1(i,j,k,l)
n = n + 1
end do
end do
end do
end do
call release(col1)
call release(col2)
call release(set)
end program example_array3data
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! In this example add dataset is created (opened) containing
! a table with 2 columns of two 4-dimensional arrays.
!
! The second array has the same data type as the first; this
! is ensured by using the arrayDataType() function to determine
! the data type of the first array.
!
! The columns are then initialised, on a row-by-row
! basis (i.e. accessing the column's data cell-by-cell),
! before the dataset is released (closed).
program example_cellarray4data
use dal
use errorhandling
implicit none
type(DataSetT) set
type(TableT) tab
type(ColumnT) col1, col2
integer(kind=INT16), dimension(:,:,:,:), pointer :: c1, c2
integer, dimension(4), parameter :: s = (/ 3,4,5,6 /)
integer :: i,j,k,l,m,n
! create a set
set = dataSet("test.dat",CREATE)
tab = addTable(set, "table", 100, "table comment" )
col1 = addColumn( tab, "column1", INTEGER16, "km", s, "column comment" )
col2 = addColumn( tab, "column2", columnDataType( col1 ), "km", s, "column comment" )
! fill with unique numbers
n = 0
do m=0,numberOfRows(tab) - 1
c1 => int16Array4Data(col1,m)
c2 => int16Array4Data(col2,m)
do l=0,5
do k=0,4
do j=0,3
do i=0,2
c1(i,j,k,l) = n
c2(i,j,k,l) = c1(i,j,k,l)
n = n + 1
end do
end do
end do
end do
end do
call release(col1)
call release(col2)
call release(set)
end program example_cellarray4data
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! In this example add dataset is created (opened) containing
! a table with 2 columns of two 4-dimensional arrays.
!
! The second array has the same data type as the first; this
! is ensured by using the arrayDataType() function to determine
! the data type of the first array.
!
! The columns are then initialised before the
! dataset is released (closed).
program example_array4data
use dal
use errorhandling
implicit none
type(DataSetT) set
type(TableT) tab
type(ColumnT) col1, col2
integer(kind=INT16), dimension(:,:,:,:,:), pointer :: c1, c2
integer, dimension(4), parameter :: s = (/ 3,4,5,6 /)
integer :: i,j,k,l,m,n
! create a set
set = dataSet("test.dat",CREATE)
tab = addTable(set, "table", 100, "table comment" )
col1 = addColumn( tab, "column1", INTEGER16, "km", s, "column comment" )
col2 = addColumn( tab, "column2", columnDataType( col1 ), "km", s, "column comment" )
! fill with unique numbers
c1 => int16Array4Data(col1)
c2 => int16Array4Data(col1)
n = 0
do m=0,numberOfRows(tab) - 1
do l=0,5
do k=0,4
do j=0,3
do i=0,2
c1(i,j,k,l,m) = n
c2(i,j,k,l,m) = c1(i,j,k,l,m)
n = n + 1
end do
end do
end do
end do
end do
call release(col1)
call release(col2)
call release(set)
end program example_array4data
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! This example shows how int16 attributes are used.
! The program creates a dataset containing two int16 attributes,
! together with a table containing two int16 attributes.
! The attributes are then accessed, by name, with
! the int16Attribute() function.
! Also, it is shown how to access the attributes by position.
program example_int16attribute
use dal
use errorhandling
implicit none
type(DataSetT) set
type(TableT) tab
type(AttributeT) att
integer i
set = dataSet("test.dat",CREATE)
call setAttribute(set,"int1",1,"int comment")
call setAttribute(set,"int2",2,"int comment")
tab = addTable(set,"table",10);
call setAttribute(tab,"int1",3,"int comment")
call setAttribute(tab,"int2",4,"int comment")
write(*,*) int16Attribute( set, "int1" ) ! output '1'
write(*,*) int16Attribute( set, "int2" ) ! output '2'
write(*,*) int16Attribute( tab, "int1" ) ! output '3'
write(*,*) int16Attribute( tab, "int2" ) ! output '4'
do i = 0, numberOfAttributes( set ) - 1
att = attribute( set, i )
write(*,*) int16Attribute( att ) ! output the sequence 1, 2
end do
call release(set)
end program example_int16attribute
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! In this example add dataset is created (opened) containing
! a table with 2 columns of two 4-dimensional arrays.
!
! The second array has the same data type as the first; this
! is ensured by using the arrayDataType() function to determine
! the data type of the first array.
!
! The columns are then initialised, and then the second column
! is output by accessing the column's data as a flat vector.
program example_int16data
use dal
use errorhandling
implicit none
type(DataSetT) set
type(TableT) tab
type(ColumnT) col1, col2
integer(kind=INT16), dimension(:,:,:,:,:), pointer :: c1, c2
integer(kind=INT16), dimension(:), pointer :: cd
integer, dimension(4), parameter :: s = (/ 3,4,5,6 /)
integer :: i,j,k,l,m,n
! create a set
set = dataSet("test.dat",CREATE)
tab = addTable(set, "table", 5, "table comment" )
col1 = addColumn( tab, "column1", INTEGER16, "km", s, "column comment" )
col2 = addColumn( tab, "column2", columnDataType( col1 ), "km", s, "column comment" )
! fill with unique numbers
c1 => int16Array4Data(col1)
c2 => int16Array4Data(col2)
n = 0
do m=0,numberOfRows(tab) - 1
do l=0,5
do k=0,4
do j=0,3
do i=0,2
c1(i,j,k,l,m) = n
c2(i,j,k,l,m) = c1(i,j,k,l,m)
n = n + 1
end do
end do
end do
end do
end do
call release(col1)
call release(col2)
! Output the col2
cd => int16Data( col2 ) ! Access the column's 4-dimensional data as a flat vector.
do n = 0,numberOfElements(col1) * numberOfRows(tab) - 1
write(*,*) cd(n)
end do
call release(col2)
call release(set)
end program example_int16data
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! In this example add dataset is created (opened) containing
! a table with 2 columns of two vector arrays.
!
! The second array has the same data type as the first; this
! is ensured by using the arrayDataType() function to determine
! the data type of the first array.
!
! The columns are then initialised, on a row-by-row
! basis (i.e. accessing the column's data cell-by-cell),
! before the dataset is released (closed).
program example_cellvectordata
use dal
use errorhandling
implicit none
type(DataSetT) set
type(TableT) tab
type(ColumnT) col1, col2
integer(kind=INT16), dimension(:), pointer :: c1, c2
integer, dimension(1), parameter :: s = (/ 3 /)
integer :: i,m,n
! create a set
set = dataSet("test.dat",CREATE)
tab = addTable(set, "table", 100, "table comment" )
col1 = addColumn( tab, "column1", INTEGER16, "km", s, "column comment" )
col2 = addColumn( tab, "column2", columnDataType( col1 ), "km", s, "column comment" )
! fill with unique numbers
n = 0
do m=0,numberOfRows(tab) - 1
c1 => int16VectorData(col1,m)
c2 => int16VectorData(col2,m)
do i=0,2
c1(i) = n
c2(i) = c1(i)
n = n + 1
end do
end do
call release(col1)
call release(col2)
call release(set)
end program example_cellvectordata
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! This example shows how to use the int16Array2Data interface.
! In the example a dataset is created (opened) containing
! a table with 2 vector arrays.
!
! The second array has the same data type as the first; this
! is ensured by using the arrayDataType() function to determine
! the data type of the first array.
!
! The array is then initialised,
program example_arrayvectordata
use dal
use errorhandling
implicit none
type(DataSetT) set
type(TableT) tab
type(ArrayT) arr1, arr2
integer(kind=INT16), dimension(:), pointer :: a1, a2
integer, dimension(1), parameter :: s = (/ 3 /)
integer :: i,n
! create a set
set = dataSet("test.dat",CREATE)
arr1 = addArray( set, "array1", INTEGER16, s, "km", "array comment" )
arr2 = addArray( set, "array2", INTEGER16, s, "km", "array comment" )
! fill with unique numbers
n = 0
a1 => int16VectorData(arr1)
a2 => int16VectorData(arr2)
do i=0,2
a1(i) = n
a2(i) = a1(i)
n = n + 1
end do
call release(arr1)
call release(arr2)
call release(set)
end program example_arrayvectordata
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! In this example add dataset is created (opened) containing
! a table with 2 columns of two vector arrays.
!
! The second column has the same data type as the first; this
! is ensured by using the columnDataType() function to determine
! the data type of the first array.
!
! The columns are then initialised before the
! dataset is released (closed).
program example_columnvectordata
use dal
use errorhandling
implicit none
type(DataSetT) set
type(TableT) tab
type(ColumnT) col1, col2
integer(kind=INT16), dimension(:,:), pointer :: c1, c2
integer, dimension(1), parameter :: s = (/ 3 /)
integer :: i,m,n
! create a set
set = dataSet("test.dat",CREATE)
tab = addTable(set, "table", 10, "table comment" )
col1 = addColumn( tab, "column1", INTEGER16, "km", s, "column comment" )
col2 = addColumn( tab, "column2", columnDataType( col1 ), "km", s, "column comment" )
! fill with unique numbers
c1 => int16VectorData(col1)
c2 => int16VectorData(col2)
n = 0
do m=0,numberOfRows(tab) - 1
do i=0,2
c1(i,m) = n
c2(i,m) = c1(i,m)
n = n + 1
end do
end do
call release(col1)
call release(col2)
call release(set)
end program example_columnvectordata
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! This example shows how to use the int32Array2Data interface.
! In the example a dataset is created (opened) containing
! a table with 2 columns of two 2-dimensional arrays.
!
! The second array has the same data type as the first; this
! is ensured by using the arrayDataType() function to determine
! the data type of the first array.
!
! The columns are then initialised, on a row-by-row
! basis (i.e. accessing the column's data cell-by-cell),
! before the dataset is released (closed).
program example_cellarray2data
use dal
use errorhandling
implicit none
type(DataSetT) set
type(TableT) tab
type(ColumnT) col1, col2
integer(kind=INT32), dimension(:,:), pointer :: c1, c2
integer, dimension(2), parameter :: s = (/ 3,4 /)
integer :: i,j,k,n
! create a set
set = dataSet("test.dat",CREATE)
tab = addTable(set, "table", 100, "table comment" )
col1 = addColumn( tab, "column1", INTEGER32, "km", s, "column comment" )
col2 = addColumn( tab, "column2", columnDataType( col1 ), "km", s, "column comment" )
! fill with unique numbers
n = 0
do k=0,numberOfRows(tab) - 1
c1 => int32Array2Data(col1,k)
c2 => int32Array2Data(col2,k)
do j=0,3
do i=0,2
c1(i,j) = n
c2(i,j) = c1(i,j)
n = n + 1
end do
end do
end do
call release(col1)
call release(col2)
call release(set)
end program example_cellarray2data
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! This example shows how to use the int32Array2Data interface.
! In the example a dataset is created (opened) containing
! a table with 2 2-dimensional arrays.
!
! The second array has the same data type as the first; this
! is ensured by using the arrayDataType() function to determine
! the data type of the first array.
!
! The columns are then initialised, on a row-by-row
! basis (i.e. accessing the column's data cell-by-cell),
! before the dataset is released (closed).
program example_arrayarray2data
use dal
use errorhandling
implicit none
type(DataSetT) set
type(TableT) tab
type(ArrayT) arr1, arr2
integer(kind=INT32), dimension(:,:), pointer :: a1, a2
integer, dimension(2), parameter :: s = (/ 3,4 /)
integer :: i,j,n
! create a set
set = dataSet("test.dat",CREATE)
arr1 = addArray( set, "array1", INTEGER32, s, "km", "array comment" )
arr2 = addArray( set, "array2", INTEGER32, s, "km", "array comment" )
! fill with unique numbers
n = 0
a1 => int32Array2Data(arr1)
a2 => int32Array2Data(arr2)
do j=0,3
do i=0,2
a1(i,j) = n
a2(i,j) = a1(i,j)
n = n + 1
end do
end do
call release(arr1)
call release(arr2)
call release(set)
end program example_arrayarray2data
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! In this example add dataset is created (opened) containing
! a table with 2 columns of two 2-dimensional arrays.
!
! The second array has the same data type as the first; this
! is ensured by using the arrayDataType() function to determine
! the data type of the first array.
!
! The columns are then initialised before the
! dataset is released (closed).
program example_array2data
use dal
use errorhandling
implicit none
type(DataSetT) set
type(TableT) tab
type(ColumnT) col1, col2
integer(kind=INT32), dimension(:,:,:), pointer :: c1, c2
integer, dimension(2), parameter :: s = (/ 3,4 /)
integer :: i,j,k,n
! create a set
set = dataSet("test.dat",CREATE)
tab = addTable(set, "table", 100, "table comment" )
col1 = addColumn( tab, "column1", INTEGER32, "km", s, "column comment" )
col2 = addColumn( tab, "column2", columnDataType( col1 ), "km", s, "column comment" )
! fill with unique numbers
c1 => int32Array2Data(col1)
c2 => int32Array2Data(col2)
n = 0
do k=0,numberOfRows(tab) - 1
do j=0,3
do i=0,2
c1(i,j,k) = n
c2(i,j,k) = c1(i,j,k)
n = n + 1
end do
end do
end do
call release(col1)
call release(col2)
call release(set)
end program example_array2data
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! In this example add dataset is created (opened) containing
! a table with 2 columns of two 3-dimensional arrays.
!
! The second array has the same data type as the first; this
! is ensured by using the arrayDataType() function to determine
! the data type of the first array.
!
! The columns are then initialised, on a row-by-row
! basis (i.e. accessing the column's data cell-by-cell),
! before the dataset is released (closed).
program example_cellarray3data
use dal
use errorhandling
implicit none
type(DataSetT) set
type(TableT) tab
type(ColumnT) col1, col2
integer(kind=INT32), dimension(:,:,:), pointer :: c1, c2
integer, dimension(3), parameter :: s = (/ 3,4,5 /)
integer :: i,j,k,l,n
! create a set
set = dataSet("test.dat",CREATE)
tab = addTable(set, "table", 100, "table comment" )
col1 = addColumn( tab, "column1", INTEGER32, "km", s, "column comment" )
col2 = addColumn( tab, "column2", columnDataType( col1 ), "km", s, "column comment" )
! fill with unique numbers
n = 0
do l=0,numberOfRows(tab) - 1
c1 => int32Array3Data(col1,l)
c2 => int32Array3Data(col2,l)
do k=0,4
do j=0,3
do i=0,2
c1(i,j,k) = n
c2(i,j,k) = c1(i,j,k)
n = n + 1
end do
end do
end do
end do
call release(col1)
call release(col2)
call release(set)
end program example_cellarray3data
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! This example shows how to use the int8Array2Data interface.
! In the example a dataset is created (opened) containing
! a table with 2 3-dimensional arrays.
!
! The second array has the same data type as the first; this
! is ensured by using the arrayDataType() function to determine
! the data type of the first array.
!
! The columns are then initialised, on a row-by-row
! basis (i.e. accessing the column's data cell-by-cell),
! before the dataset is released (closed).
program example_arrayarray3data
use dal
use errorhandling
implicit none
type(DataSetT) set
type(TableT) tab
type(ArrayT) arr1, arr2
integer(kind=INT32), dimension(:,:,:), pointer :: a1, a2
integer, dimension(3), parameter :: s = (/ 3,4,5 /)
integer :: i,j,k,n
! create a set
set = dataSet("test.dat",CREATE)
arr1 = addArray( set, "array1", INTEGER32, s, "km", "array comment" )
arr2 = addArray( set, "array2", INTEGER32, s, "km", "array comment" )
! fill with unique numbers
n = 0
a1 => int32Array3Data(arr1)
a2 => int32Array3Data(arr2)
do k=0,4
do j=0,3
do i=0,2
a1(i,j,k) = n
a2(i,j,k) = a1(i,j,k)
n = n + 1
end do
end do
end do
call release(arr1)
call release(arr2)
call release(set)
end program example_arrayarray3data
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! In this example add dataset is created (opened) containing
! a table with 2 columns of two 3-dimensional arrays.
!
! The second array has the same data type as the first; this
! is ensured by using the arrayDataType() function to determine
! the data type of the first array.
!
! The columns are then initialised before the
! dataset is released (closed).
program example_array3data
use dal
use errorhandling
implicit none
type(DataSetT) set
type(TableT) tab
type(ColumnT) col1, col2
integer(kind=INT32), dimension(:,:,:,:), pointer :: c1, c2
integer, dimension(3), parameter :: s = (/ 3,4,5 /)
integer :: i,j,k,l,n
! create a set
set = dataSet("test.dat",CREATE)
tab = addTable(set, "table", 100, "table comment" )
col1 = addColumn( tab, "column1", INTEGER32, "km", s, "column comment" )
col2 = addColumn( tab, "column2", columnDataType( col1 ), "km", s, "column comment" )
! fill with unique numbers
c1 => int32Array3Data(col1)
c2 => int32Array3Data(col1)
n = 0
do l=0,numberOfRows(tab) - 1
do k = 0,4
do j=0,3
do i=0,2
c1(i,j,k,l) = n
c2(i,j,k,l) = c1(i,j,k,l)
n = n + 1
end do
end do
end do
end do
call release(col1)
call release(col2)
call release(set)
end program example_array3data
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! In this example add dataset is created (opened) containing
! a table with 2 columns of two 4-dimensional arrays.
!
! The second array has the same data type as the first; this
! is ensured by using the arrayDataType() function to determine
! the data type of the first array.
!
! The columns are then initialised, on a row-by-row
! basis (i.e. accessing the column's data cell-by-cell),
! before the dataset is released (closed).
program example_cellarray4data
use dal
use errorhandling
implicit none
type(DataSetT) set
type(TableT) tab
type(ColumnT) col1, col2
integer(kind=INT32), dimension(:,:,:,:), pointer :: c1, c2
integer, dimension(4), parameter :: s = (/ 3,4,5,6 /)
integer :: i,j,k,l,m,n
! create a set
set = dataSet("test.dat",CREATE)
tab = addTable(set, "table", 100, "table comment" )
col1 = addColumn( tab, "column1", INTEGER32, "km", s, "column comment" )
col2 = addColumn( tab, "column2", columnDataType( col1 ), "km", s, "column comment" )
! fill with unique numbers
n = 0
do m=0,numberOfRows(tab) - 1
c1 => int32Array4Data(col1,m)
c2 => int32Array4Data(col2,m)
do l=0,5
do k=0,4
do j=0,3
do i=0,2
c1(i,j,k,l) = n
c2(i,j,k,l) = c1(i,j,k,l)
n = n + 1
end do
end do
end do
end do
end do
call release(col1)
call release(col2)
call release(set)
end program example_cellarray4data
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! In this example add dataset is created (opened) containing
! a table with 2 columns of two 4-dimensional arrays.
!
! The second array has the same data type as the first; this
! is ensured by using the arrayDataType() function to determine
! the data type of the first array.
!
! The columns are then initialised before the
! dataset is released (closed).
program example_array4data
use dal
use errorhandling
implicit none
type(DataSetT) set
type(TableT) tab
type(ColumnT) col1, col2
integer(kind=INT32), dimension(:,:,:,:,:), pointer :: c1, c2
integer, dimension(4), parameter :: s = (/ 3,4,5,6 /)
integer :: i,j,k,l,m,n
! create a set
set = dataSet("test.dat",CREATE)
tab = addTable(set, "table", 100, "table comment" )
col1 = addColumn( tab, "column1", INTEGER32, "km", s, "column comment" )
col2 = addColumn( tab, "column2", columnDataType( col1 ), "km", s, "column comment" )
! fill with unique numbers
c1 => int32Array4Data(col1)
c2 => int32Array4Data(col1)
n = 0
do m=0,numberOfRows(tab) - 1
do l=0,5
do k=0,4
do j=0,3
do i=0,2
c1(i,j,k,l,m) = n
c2(i,j,k,l,m) = c1(i,j,k,l,m)
n = n + 1
end do
end do
end do
end do
end do
call release(col1)
call release(col2)
call release(set)
end program example_array4data
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! This example shows how int32 attributes are used.
! The program creates a dataset containing two int32 attributes,
! together with a table containing two int32 attributes.
! The attributes are then accessed, by name, with
! the int32Attribute() function.
! Also, it is shown how to access the attributes by position.
program example_int32attribute
use dal
use errorhandling
implicit none
type(DataSetT) set
type(TableT) tab
type(AttributeT) att
integer i
set = dataSet("test.dat",CREATE)
call setAttribute(set,"int1",1,"int comment")
call setAttribute(set,"int2",2,"int comment")
tab = addTable(set,"table",10);
call setAttribute(tab,"int1",3,"int comment")
call setAttribute(tab,"int2",4,"int comment")
write(*,*) int32Attribute( set, "int1" ) ! output '1'
write(*,*) int32Attribute( set, "int2" ) ! output '2'
write(*,*) int32Attribute( tab, "int1" ) ! output '3'
write(*,*) int32Attribute( tab, "int2" ) ! output '4'
do i = 0, numberOfAttributes( set ) - 1
att = attribute( set, i )
write(*,*) int32Attribute( att ) ! output the sequence 1, 2
end do
call release(set)
end program example_int32attribute
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! In this example add dataset is created (opened) containing
! a table with 2 columns of two 4-dimensional arrays.
!
! The second array has the same data type as the first; this
! is ensured by using the arrayDataType() function to determine
! the data type of the first array.
!
! The columns are then initialised, and then the second column
! is output by accessing the column's data as a flat vector.
program example_int32data
use dal
use errorhandling
implicit none
type(DataSetT) set
type(TableT) tab
type(ColumnT) col1, col2
integer(kind=INT32), dimension(:,:,:,:,:), pointer :: c1, c2
integer(kind=INT32), dimension(:), pointer :: cd
integer, dimension(4), parameter :: s = (/ 3,4,5,6 /)
integer :: i,j,k,l,m,n
! create a set
set = dataSet("test.dat",CREATE)
tab = addTable(set, "table", 5, "table comment" )
col1 = addColumn( tab, "column1", INTEGER32, "km", s, "column comment" )
col2 = addColumn( tab, "column2", columnDataType( col1 ), "km", s, "column comment" )
! fill with unique numbers
c1 => int32Array4Data(col1)
c2 => int32Array4Data(col2)
n = 0
do m=0,numberOfRows(tab) - 1
do l=0,5
do k=0,4
do j=0,3
do i=0,2
c1(i,j,k,l,m) = n
c2(i,j,k,l,m) = c1(i,j,k,l,m)
n = n + 1
end do
end do
end do
end do
end do
call release(col1)
call release(col2)
! Output the col2
cd => int32Data( col2 ) ! Access the column's 4-dimensional data as a flat vector.
do n = 0,numberOfElements(col1) * numberOfRows(tab) - 1
write(*,*) cd(n)
end do
call release(col2)
call release(set)
end program example_int32data
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! In this example add dataset is created (opened) containing
! a table with 2 columns of two vector arrays.
!
! The second array has the same data type as the first; this
! is ensured by using the arrayDataType() function to determine
! the data type of the first array.
!
! The columns are then initialised, on a row-by-row
! basis (i.e. accessing the column's data cell-by-cell),
! before the dataset is released (closed).
program example_cellvectordata
use dal
use errorhandling
implicit none
type(DataSetT) set
type(TableT) tab
type(ColumnT) col1, col2
integer(kind=INT32), dimension(:), pointer :: c1, c2
integer, dimension(1), parameter :: s = (/ 3 /)
integer :: i,m,n
! create a set
set = dataSet("test.dat",CREATE)
tab = addTable(set, "table", 100, "table comment" )
col1 = addColumn( tab, "column1", INTEGER32, "km", s, "column comment" )
col2 = addColumn( tab, "column2", columnDataType( col1 ), "km", s, "column comment" )
! fill with unique numbers
n = 0
do m=0,numberOfRows(tab) - 1
c1 => int32VectorData(col1,m)
c2 => int32VectorData(col2,m)
do i=0,2
c1(i) = n
c2(i) = c1(i)
n = n + 1
end do
end do
call release(col1)
call release(col2)
call release(set)
end program example_cellvectordata
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! This example shows how to use the int32Array2Data interface.
! In the example a dataset is created (opened) containing
! a table with 2 vector arrays.
!
! The second array has the same data type as the first; this
! is ensured by using the arrayDataType() function to determine
! the data type of the first array.
!
! The array is then initialised,
program example_arrayvectordata
use dal
use errorhandling
implicit none
type(DataSetT) set
type(TableT) tab
type(ArrayT) arr1, arr2
integer(kind=INT32), dimension(:), pointer :: a1, a2
integer, dimension(1), parameter :: s = (/ 3 /)
integer :: i,n
! create a set
set = dataSet("test.dat",CREATE)
arr1 = addArray( set, "array1", INTEGER32, s, "km", "array comment" )
arr2 = addArray( set, "array2", INTEGER32, s, "km", "array comment" )
! fill with unique numbers
n = 0
a1 => int32VectorData(arr1)
a2 => int32VectorData(arr2)
do i=0,2
a1(i) = n
a2(i) = a1(i)
n = n + 1
end do
call release(arr1)
call release(arr2)
call release(set)
end program example_arrayvectordata
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! In this example add dataset is created (opened) containing
! a table with 2 columns of two vector arrays.
!
! The second column has the same data type as the first; this
! is ensured by using the columnDataType() function to determine
! the data type of the first array.
!
! The columns are then initialised before the
! dataset is released (closed).
program example_columnvectordata
use dal
use errorhandling
implicit none
type(DataSetT) set
type(TableT) tab
type(ColumnT) col1, col2
integer(kind=INT32), dimension(:,:), pointer :: c1, c2
integer, dimension(1), parameter :: s = (/ 3 /)
integer :: i,m,n
! create a set
set = dataSet("test.dat",CREATE)
tab = addTable(set, "table", 10, "table comment" )
col1 = addColumn( tab, "column1", INTEGER32, "km", s, "column comment" )
col2 = addColumn( tab, "column2", columnDataType( col1 ), "km", s, "column comment" )
! fill with unique numbers
c1 => int32VectorData(col1)
c2 => int32VectorData(col2)
n = 0
do m=0,numberOfRows(tab) - 1
do i=0,2
c1(i,m) = n
c2(i,m) = c1(i,m)
n = n + 1
end do
end do
call release(col1)
call release(col2)
call release(set)
end program example_columnvectordata
The null value of an object containing integer data, may be defined with a call to setNullValue().
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! This example shows how null values are used.
subroutine check( thisNullable )
use dal
type(NullableT), intent(in) :: thisNullable
write(*,*) "Null defined?: ", nullDefined( thisNullable ), nullType( thisNullable )
end subroutine check
program example_nullvalues
use dal
use errorhandling
implicit none
type(DataSetT) set
type(ArrayT) arr1, arr2
type(TableT) tab
type(ColumnT) col1, col2
integer(kind=int32), dimension(:), pointer :: i32
real(kind=double), dimension(:), pointer :: r64
integer(kind=int32), dimension(:,:,:), pointer :: a1, a2
integer, dimension(3), parameter :: s = (/ 3,4,2 /)
integer :: i,j,k,n
! create a set
set = dataSet("test.dat",CREATE)
arr1 = addArray(set, "array1", INTEGER32, dimensions=s )
arr2 = addArray(set, "array2", arrayDataType( arr1 ), dimensions=s )
! fill with unique numbers
a1 => int32Array3Data(arr1)
a2 => int32Array3Data(arr1)
n = 0
do k=0,1
do j=0,3
do i=0,2
a1(i,j,k) = n
a2(i,j,k) = a1(i,j,k) + 1
n = n + 1
end do
end do
end do
call setNullValue( arr1, 999999 )
call check( nullable( arr1 ) )
call setToNull( arr1, 0 ) ! Set the first element of array arr1 to null.
! Would have given an error, if the null
! value of array arr1 had not been set.
if( nullType( arr1 ) .eq. INTEGER_NULL ) then !
write(*,*) "Using null value of arr1, in arr2"
call setNullValue( arr2, intNullValue( arr1 ))
else
call setNullValue( arr2, 999999 )
end if
call check( nullable( arr2 ) )
call setToNull( arr2, 1 ) ! Set the second element of array arr2 to null.
! Would have given an error, if the null
! value of array arr2 had not been set.
call release(arr1)
call release(arr2)
tab = addTable(set,"some table",100)
col1 = addColumn(tab,"int32",INTEGER32,units="m",comment="in32 column")
i32 => int32Data(col1)
do i=0,numberOfRows(tab)-1
i32(i) = 3*i
end do
call setNullValue( col1, 999999 )
call check( nullable( col1 ) )
call setToNull( col1, 0 ) ! Set the first element of column col1 to null.
col2 = addColumn(tab,"real64",REAL64,units="hm",comment="real64 column")
r64 => real64Data(col2)
do i=0,numberOfRows(tab)-1
r64(i) = 0.25*i
end do
! col is a non-integer column and it would be an
! an error to call setNullValue().
call check( nullable( col2 ) )
call setToNull( col2, 0 ) ! Set the first element of column col2 to null.
if( hasNulls( col2 ) ) then
do i=0,numberOfRows(tab)-1
if( isNull( col2, i ) ) then
write(*,*) "element", i, "is null"
else
write(*,*) "element", i, "is", r64(i)
endif
end do
endif
call release(col1)
call release(col2)
call release(set)
end program example_nullvalues
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! This example shows how null values are used.
subroutine check( thisNullable )
use dal
type(NullableT), intent(in) :: thisNullable
write(*,*) "Null defined?: ", nullDefined( thisNullable ), nullType( thisNullable )
end subroutine check
program example_nullvalues
use dal
use errorhandling
implicit none
type(DataSetT) set
type(ArrayT) arr1, arr2
type(TableT) tab
type(ColumnT) col1, col2
integer(kind=int32), dimension(:), pointer :: i32
real(kind=double), dimension(:), pointer :: r64
integer(kind=int32), dimension(:,:,:), pointer :: a1, a2
integer, dimension(3), parameter :: s = (/ 3,4,2 /)
integer :: i,j,k,n
! create a set
set = dataSet("test.dat",CREATE)
arr1 = addArray(set, "array1", INTEGER32, dimensions=s )
arr2 = addArray(set, "array2", arrayDataType( arr1 ), dimensions=s )
! fill with unique numbers
a1 => int32Array3Data(arr1)
a2 => int32Array3Data(arr1)
n = 0
do k=0,1
do j=0,3
do i=0,2
a1(i,j,k) = n
a2(i,j,k) = a1(i,j,k) + 1
n = n + 1
end do
end do
end do
call setNullValue( arr1, 999999 )
call check( nullable( arr1 ) )
call setToNull( arr1, 0 ) ! Set the first element of array arr1 to null.
! Would have given an error, if the null
! value of array arr1 had not been set.
if( nullType( arr1 ) .eq. INTEGER_NULL ) then !
write(*,*) "Using null value of arr1, in arr2"
call setNullValue( arr2, intNullValue( arr1 ))
else
call setNullValue( arr2, 999999 )
end if
call check( nullable( arr2 ) )
call setToNull( arr2, 1 ) ! Set the second element of array arr2 to null.
! Would have given an error, if the null
! value of array arr2 had not been set.
call release(arr1)
call release(arr2)
tab = addTable(set,"some table",100)
col1 = addColumn(tab,"int32",INTEGER32,units="m",comment="in32 column")
i32 => int32Data(col1)
do i=0,numberOfRows(tab)-1
i32(i) = 3*i
end do
call setNullValue( col1, 999999 )
call check( nullable( col1 ) )
call setToNull( col1, 0 ) ! Set the first element of column col1 to null.
col2 = addColumn(tab,"real64",REAL64,units="hm",comment="real64 column")
r64 => real64Data(col2)
do i=0,numberOfRows(tab)-1
r64(i) = 0.25*i
end do
! col is a non-integer column and it would be an
! an error to call setNullValue().
call check( nullable( col2 ) )
call setToNull( col2, 0 ) ! Set the first element of column col2 to null.
if( hasNulls( col2 ) ) then
do i=0,numberOfRows(tab)-1
if( isNull( col2, i ) ) then
write(*,*) "element", i, "is null"
else
write(*,*) "element", i, "is", r64(i)
endif
end do
endif
call release(col1)
call release(col2)
call release(set)
end program example_nullvalues
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! This example shows how null values are used.
subroutine check( thisNullable )
use dal
type(NullableT), intent(in) :: thisNullable
write(*,*) "Null defined?: ", nullDefined( thisNullable ), nullType( thisNullable )
end subroutine check
program example_nullvalues
use dal
use errorhandling
implicit none
type(DataSetT) set
type(ArrayT) arr1, arr2
type(TableT) tab
type(ColumnT) col1, col2
integer(kind=int32), dimension(:), pointer :: i32
real(kind=double), dimension(:), pointer :: r64
integer(kind=int32), dimension(:,:,:), pointer :: a1, a2
integer, dimension(3), parameter :: s = (/ 3,4,2 /)
integer :: i,j,k,n
! create a set
set = dataSet("test.dat",CREATE)
arr1 = addArray(set, "array1", INTEGER32, dimensions=s )
arr2 = addArray(set, "array2", arrayDataType( arr1 ), dimensions=s )
! fill with unique numbers
a1 => int32Array3Data(arr1)
a2 => int32Array3Data(arr1)
n = 0
do k=0,1
do j=0,3
do i=0,2
a1(i,j,k) = n
a2(i,j,k) = a1(i,j,k) + 1
n = n + 1
end do
end do
end do
call setNullValue( arr1, 999999 )
call check( nullable( arr1 ) )
call setToNull( arr1, 0 ) ! Set the first element of array arr1 to null.
! Would have given an error, if the null
! value of array arr1 had not been set.
if( nullType( arr1 ) .eq. INTEGER_NULL ) then !
write(*,*) "Using null value of arr1, in arr2"
call setNullValue( arr2, intNullValue( arr1 ))
else
call setNullValue( arr2, 999999 )
end if
call check( nullable( arr2 ) )
call setToNull( arr2, 1 ) ! Set the second element of array arr2 to null.
! Would have given an error, if the null
! value of array arr2 had not been set.
call release(arr1)
call release(arr2)
tab = addTable(set,"some table",100)
col1 = addColumn(tab,"int32",INTEGER32,units="m",comment="in32 column")
i32 => int32Data(col1)
do i=0,numberOfRows(tab)-1
i32(i) = 3*i
end do
call setNullValue( col1, 999999 )
call check( nullable( col1 ) )
call setToNull( col1, 0 ) ! Set the first element of column col1 to null.
col2 = addColumn(tab,"real64",REAL64,units="hm",comment="real64 column")
r64 => real64Data(col2)
do i=0,numberOfRows(tab)-1
r64(i) = 0.25*i
end do
! col is a non-integer column and it would be an
! an error to call setNullValue().
call check( nullable( col2 ) )
call setToNull( col2, 0 ) ! Set the first element of column col2 to null.
if( hasNulls( col2 ) ) then
do i=0,numberOfRows(tab)-1
if( isNull( col2, i ) ) then
write(*,*) "element", i, "is null"
else
write(*,*) "element", i, "is", r64(i)
endif
end do
endif
call release(col1)
call release(col2)
call release(set)
end program example_nullvalues
This subroutine must only be called by Meta Tasks.
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! This example shows how to use the keepDataSet
! subroutine
program example_keepdiscarddataset
use dal
implicit none
type(DataSetT) set
set = dataSet("test.dat",CREATE)
call release(set) ! The dataset will be released from memory
call keepDataSet("test.dat") ! Tell the dataset server not to discard
! the dataset with name "test.dat"
set = dataSet("test.dat",READ)
call release(set) ! The dataset will not be released from memory
set = dataSet("test.dat",READ) ! The dataset is already in memory, so this
! operation has virtually no overhead.
call release(set) ! The dataset will not be released from memory
call discardDataSet("test.dat") ! Tell the dataset server to discard and
! release the dataset with name "test.dat"
end program example_keepdiscarddataset
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! This example shows how the label, relabel, name and rename interfaces are used.
subroutine displayLabelled( l )
use dal
implicit none
type(LabelledT), intent(in) :: l
write(*,*) "the object with name ", name( l ), " has label: ", label(l)
end subroutine displayLabelled
subroutine display( set )
use dal
implicit none
type(DataSetT) set
type(ArrayT) arr
type(TableT) tab
type(ColumnT) col
type(AttributeT) att
att = attribute( set, 0 )
write(*,*) name(att), label( att )
call displayLabelled( labelled( att ) )
arr = array( set, 0, READ )
write(*,*) name(arr), label( arr )
call displayLabelled( labelled( arr ) )
att = attribute( arr, 0 )
write(*,*) name(att), label( att )
call displayLabelled( labelled( att ) )
tab = table( set, 1 )
write(*,*) name(tab), label( tab )
call displayLabelled( labelled( tab ) )
att = attribute( tab, 0 )
write(*,*) name(att), label( att )
call displayLabelled( labelled( att ) )
col = column( tab, 0, READ )
write(*,*) name(col), label( col )
call displayLabelled( labelled( col ) )
att = attribute( col, 0 )
write(*,*) name(att), label( att )
call displayLabelled( labelled( att ) )
end subroutine display
program example_labelled
use dal
implicit none
type(DataSetT) set
type(ArrayT) arr
type(TableT) tab
type(ColumnT) col
! type(AttributeT) att
! integer(kind=int32), dimension(:,:,:), pointer :: a
integer, dimension(3), parameter :: s = (/ 3,4,2 /)
! create a set
set = dataSet("test.dat",CREATE)
call setAttribute(set,"att1","value1","a dataset attribute comment")
arr = addArray(set, "array", INTEGER32, comment="an array comment", dimensions=s )
call setAttribute(arr,"att2","value2","an array attribute comment")
tab = addTable(set, "table", 10, comment="a table comment" )
call setAttribute(tab,"att3","value3","a table attribute comment")
col = addColumn(tab,"int8",INTEGER8,comment="a column comment")
call setAttribute(col,"TLMAX","value4","a column attribute comment")
call display( set )
call relabel( tab, "a new table comment" )
call rename( col, "newcolnm" )
call display( set )
call release( set )
end program example_labelled
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! This example shows how the label, relabel, name and rename interfaces are used.
subroutine displayLabelled( l )
use dal
implicit none
type(LabelledT), intent(in) :: l
write(*,*) "the object with name ", name( l ), " has label: ", label(l)
end subroutine displayLabelled
subroutine display( set )
use dal
implicit none
type(DataSetT) set
type(ArrayT) arr
type(TableT) tab
type(ColumnT) col
type(AttributeT) att
att = attribute( set, 0 )
write(*,*) name(att), label( att )
call displayLabelled( labelled( att ) )
arr = array( set, 0, READ )
write(*,*) name(arr), label( arr )
call displayLabelled( labelled( arr ) )
att = attribute( arr, 0 )
write(*,*) name(att), label( att )
call displayLabelled( labelled( att ) )
tab = table( set, 1 )
write(*,*) name(tab), label( tab )
call displayLabelled( labelled( tab ) )
att = attribute( tab, 0 )
write(*,*) name(att), label( att )
call displayLabelled( labelled( att ) )
col = column( tab, 0, READ )
write(*,*) name(col), label( col )
call displayLabelled( labelled( col ) )
att = attribute( col, 0 )
write(*,*) name(att), label( att )
call displayLabelled( labelled( att ) )
end subroutine display
program example_labelled
use dal
implicit none
type(DataSetT) set
type(ArrayT) arr
type(TableT) tab
type(ColumnT) col
! type(AttributeT) att
! integer(kind=int32), dimension(:,:,:), pointer :: a
integer, dimension(3), parameter :: s = (/ 3,4,2 /)
! create a set
set = dataSet("test.dat",CREATE)
call setAttribute(set,"att1","value1","a dataset attribute comment")
arr = addArray(set, "array", INTEGER32, comment="an array comment", dimensions=s )
call setAttribute(arr,"att2","value2","an array attribute comment")
tab = addTable(set, "table", 10, comment="a table comment" )
call setAttribute(tab,"att3","value3","a table attribute comment")
col = addColumn(tab,"int8",INTEGER8,comment="a column comment")
call setAttribute(col,"TLMAX","value4","a column attribute comment")
call display( set )
call relabel( tab, "a new table comment" )
call rename( col, "newcolnm" )
call display( set )
call release( set )
end program example_labelled
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! This example shows how the label, relabel, name and rename interfaces are used.
subroutine displayLabelled( l )
use dal
implicit none
type(LabelledT), intent(in) :: l
write(*,*) "the object with name ", name( l ), " has label: ", label(l)
end subroutine displayLabelled
subroutine display( set )
use dal
implicit none
type(DataSetT) set
type(ArrayT) arr
type(TableT) tab
type(ColumnT) col
type(AttributeT) att
att = attribute( set, 0 )
write(*,*) name(att), label( att )
call displayLabelled( labelled( att ) )
arr = array( set, 0, READ )
write(*,*) name(arr), label( arr )
call displayLabelled( labelled( arr ) )
att = attribute( arr, 0 )
write(*,*) name(att), label( att )
call displayLabelled( labelled( att ) )
tab = table( set, 1 )
write(*,*) name(tab), label( tab )
call displayLabelled( labelled( tab ) )
att = attribute( tab, 0 )
write(*,*) name(att), label( att )
call displayLabelled( labelled( att ) )
col = column( tab, 0, READ )
write(*,*) name(col), label( col )
call displayLabelled( labelled( col ) )
att = attribute( col, 0 )
write(*,*) name(att), label( att )
call displayLabelled( labelled( att ) )
end subroutine display
program example_labelled
use dal
implicit none
type(DataSetT) set
type(ArrayT) arr
type(TableT) tab
type(ColumnT) col
! type(AttributeT) att
! integer(kind=int32), dimension(:,:,:), pointer :: a
integer, dimension(3), parameter :: s = (/ 3,4,2 /)
! create a set
set = dataSet("test.dat",CREATE)
call setAttribute(set,"att1","value1","a dataset attribute comment")
arr = addArray(set, "array", INTEGER32, comment="an array comment", dimensions=s )
call setAttribute(arr,"att2","value2","an array attribute comment")
tab = addTable(set, "table", 10, comment="a table comment" )
call setAttribute(tab,"att3","value3","a table attribute comment")
col = addColumn(tab,"int8",INTEGER8,comment="a column comment")
call setAttribute(col,"TLMAX","value4","a column attribute comment")
call display( set )
call relabel( tab, "a new table comment" )
call rename( col, "newcolnm" )
call display( set )
call release( set )
end program example_labelled
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! This example shows how the mode()
! function is used.
function addTableToSet( s, n, r )
use dal
implicit none
type(DataSetT), intent(in) :: s
character(len=*), intent(in) :: n
integer, intent(in) :: r
type(TableT) :: addTableToSet
if( mode( s ).eq.READ ) then
write(*,*) 'The table with name ', n, ' is read only'
else
addTableToSet = addTable(s,n,r)
end if
end function addTableToSet
program example_mode
use dal
implicit none
type(DataSetT) set
type(TableT) tab
type(BlockT) blk
integer i
type(TableT) :: addTableToSet
set = dataSet("test.dat",CREATE)
tab = addTableToSet(set,"table1",10)
call release( set )
set = dataSet("test.dat",READ)
tab = addTableToSet(set,"table2",10)
call release( set )
end program example_mode
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! This example shows how the label, relabel, name and rename interfaces are used.
subroutine displayLabelled( l )
use dal
implicit none
type(LabelledT), intent(in) :: l
write(*,*) "the object with name ", name( l ), " has label: ", label(l)
end subroutine displayLabelled
subroutine display( set )
use dal
implicit none
type(DataSetT) set
type(ArrayT) arr
type(TableT) tab
type(ColumnT) col
type(AttributeT) att
att = attribute( set, 0 )
write(*,*) name(att), label( att )
call displayLabelled( labelled( att ) )
arr = array( set, 0, READ )
write(*,*) name(arr), label( arr )
call displayLabelled( labelled( arr ) )
att = attribute( arr, 0 )
write(*,*) name(att), label( att )
call displayLabelled( labelled( att ) )
tab = table( set, 1 )
write(*,*) name(tab), label( tab )
call displayLabelled( labelled( tab ) )
att = attribute( tab, 0 )
write(*,*) name(att), label( att )
call displayLabelled( labelled( att ) )
col = column( tab, 0, READ )
write(*,*) name(col), label( col )
call displayLabelled( labelled( col ) )
att = attribute( col, 0 )
write(*,*) name(att), label( att )
call displayLabelled( labelled( att ) )
end subroutine display
program example_labelled
use dal
implicit none
type(DataSetT) set
type(ArrayT) arr
type(TableT) tab
type(ColumnT) col
! type(AttributeT) att
! integer(kind=int32), dimension(:,:,:), pointer :: a
integer, dimension(3), parameter :: s = (/ 3,4,2 /)
! create a set
set = dataSet("test.dat",CREATE)
call setAttribute(set,"att1","value1","a dataset attribute comment")
arr = addArray(set, "array", INTEGER32, comment="an array comment", dimensions=s )
call setAttribute(arr,"att2","value2","an array attribute comment")
tab = addTable(set, "table", 10, comment="a table comment" )
call setAttribute(tab,"att3","value3","a table attribute comment")
col = addColumn(tab,"int8",INTEGER8,comment="a column comment")
call setAttribute(col,"TLMAX","value4","a column attribute comment")
call display( set )
call relabel( tab, "a new table comment" )
call rename( col, "newcolnm" )
call display( set )
call release( set )
end program example_labelled
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! This example illustrates the use of the dataComponent() function.
! The units of objects with data type BOOLEAN and STRING are meaningless
! and so are not displayed.
subroutine displayUnits( dcomponent )
use dal
implicit none
type(DataComponentT) dcomponent
integer dattype
dattype = dataType( dcomponent )
write(*,*) dattype
if(dattype.eq.INTEGER8.or.dattype.eq.INTEGER16.or.dattype.eq.INTEGER32 &
.or.dattype.eq.REAL32.or.dattype.eq.REAL64) then
write(*,*) units( dcomponent )
end if
end subroutine displayUnits
program example_datacomponent
use dal
implicit none
type(ArrayT) arr
type(BlockT) blk
type(ColumnT) col
type(DataSetT) set
type(TableT) tab
integer i, j
integer, dimension(3), parameter :: s = (/ 2,3,4 /)
set = dataSet("test.dat",CREATE)
tab = addTable(set,"some table",100)
col = addColumn(tab,"bool",BOOLEAN)
col = addColumn(tab,"int8",INTEGER8,units="cm",comment="int8 column")
col = addColumn(tab,"int16",INTEGER16,units="dm",comment="int16 column")
col = addColumn(tab,"int32",INTEGER32,units="m",comment="in32 column")
col = addColumn(tab,"real32",REAL32,units="Dm",comment="real32 column")
col = addColumn(tab,"real64",REAL64,units="hm",comment="real64 column")
col = addColumn(tab,"string",STRING,comment="string column",dimensions=(/80/))
arr = addArray(set, "array1", INTEGER16, dimensions=s, units="klm" )
arr = addArray(set, "array2", INTEGER32, dimensions=s, units="kla" )
do i = 0, numberOfBlocks( set ) - 1
blk = block( set, i, READ )
if( blockType( blk ).eq.ARRAY_BLOCK ) then
arr = array( set, name( blk ), READ )
call displayUnits( dataComponent( arr ) )
else
tab = table( set, name( blk ) )
do j = 0, numberOfColumns( tab ) - 1
col = column( tab, j, READ )
call displayUnits( dataComponent( col ) )
end do
end if
end do
call release(set)
end program example_datacomponent
For real objects, this function always returns true.
The null value of an object containing integer data may be defined by calling setNullValue().
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! This example shows how null values are used.
subroutine check( thisNullable )
use dal
type(NullableT), intent(in) :: thisNullable
write(*,*) "Null defined?: ", nullDefined( thisNullable ), nullType( thisNullable )
end subroutine check
program example_nullvalues
use dal
use errorhandling
implicit none
type(DataSetT) set
type(ArrayT) arr1, arr2
type(TableT) tab
type(ColumnT) col1, col2
integer(kind=int32), dimension(:), pointer :: i32
real(kind=double), dimension(:), pointer :: r64
integer(kind=int32), dimension(:,:,:), pointer :: a1, a2
integer, dimension(3), parameter :: s = (/ 3,4,2 /)
integer :: i,j,k,n
! create a set
set = dataSet("test.dat",CREATE)
arr1 = addArray(set, "array1", INTEGER32, dimensions=s )
arr2 = addArray(set, "array2", arrayDataType( arr1 ), dimensions=s )
! fill with unique numbers
a1 => int32Array3Data(arr1)
a2 => int32Array3Data(arr1)
n = 0
do k=0,1
do j=0,3
do i=0,2
a1(i,j,k) = n
a2(i,j,k) = a1(i,j,k) + 1
n = n + 1
end do
end do
end do
call setNullValue( arr1, 999999 )
call check( nullable( arr1 ) )
call setToNull( arr1, 0 ) ! Set the first element of array arr1 to null.
! Would have given an error, if the null
! value of array arr1 had not been set.
if( nullType( arr1 ) .eq. INTEGER_NULL ) then !
write(*,*) "Using null value of arr1, in arr2"
call setNullValue( arr2, intNullValue( arr1 ))
else
call setNullValue( arr2, 999999 )
end if
call check( nullable( arr2 ) )
call setToNull( arr2, 1 ) ! Set the second element of array arr2 to null.
! Would have given an error, if the null
! value of array arr2 had not been set.
call release(arr1)
call release(arr2)
tab = addTable(set,"some table",100)
col1 = addColumn(tab,"int32",INTEGER32,units="m",comment="in32 column")
i32 => int32Data(col1)
do i=0,numberOfRows(tab)-1
i32(i) = 3*i
end do
call setNullValue( col1, 999999 )
call check( nullable( col1 ) )
call setToNull( col1, 0 ) ! Set the first element of column col1 to null.
col2 = addColumn(tab,"real64",REAL64,units="hm",comment="real64 column")
r64 => real64Data(col2)
do i=0,numberOfRows(tab)-1
r64(i) = 0.25*i
end do
! col is a non-integer column and it would be an
! an error to call setNullValue().
call check( nullable( col2 ) )
call setToNull( col2, 0 ) ! Set the first element of column col2 to null.
if( hasNulls( col2 ) ) then
do i=0,numberOfRows(tab)-1
if( isNull( col2, i ) ) then
write(*,*) "element", i, "is null"
else
write(*,*) "element", i, "is", r64(i)
endif
end do
endif
call release(col1)
call release(col2)
call release(set)
end program example_nullvalues
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! This example shows how null values are used.
subroutine check( thisNullable )
use dal
type(NullableT), intent(in) :: thisNullable
write(*,*) "Null defined?: ", nullDefined( thisNullable ), nullType( thisNullable )
end subroutine check
program example_nullvalues
use dal
use errorhandling
implicit none
type(DataSetT) set
type(ArrayT) arr1, arr2
type(TableT) tab
type(ColumnT) col1, col2
integer(kind=int32), dimension(:), pointer :: i32
real(kind=double), dimension(:), pointer :: r64
integer(kind=int32), dimension(:,:,:), pointer :: a1, a2
integer, dimension(3), parameter :: s = (/ 3,4,2 /)
integer :: i,j,k,n
! create a set
set = dataSet("test.dat",CREATE)
arr1 = addArray(set, "array1", INTEGER32, dimensions=s )
arr2 = addArray(set, "array2", arrayDataType( arr1 ), dimensions=s )
! fill with unique numbers
a1 => int32Array3Data(arr1)
a2 => int32Array3Data(arr1)
n = 0
do k=0,1
do j=0,3
do i=0,2
a1(i,j,k) = n
a2(i,j,k) = a1(i,j,k) + 1
n = n + 1
end do
end do
end do
call setNullValue( arr1, 999999 )
call check( nullable( arr1 ) )
call setToNull( arr1, 0 ) ! Set the first element of array arr1 to null.
! Would have given an error, if the null
! value of array arr1 had not been set.
if( nullType( arr1 ) .eq. INTEGER_NULL ) then !
write(*,*) "Using null value of arr1, in arr2"
call setNullValue( arr2, intNullValue( arr1 ))
else
call setNullValue( arr2, 999999 )
end if
call check( nullable( arr2 ) )
call setToNull( arr2, 1 ) ! Set the second element of array arr2 to null.
! Would have given an error, if the null
! value of array arr2 had not been set.
call release(arr1)
call release(arr2)
tab = addTable(set,"some table",100)
col1 = addColumn(tab,"int32",INTEGER32,units="m",comment="in32 column")
i32 => int32Data(col1)
do i=0,numberOfRows(tab)-1
i32(i) = 3*i
end do
call setNullValue( col1, 999999 )
call check( nullable( col1 ) )
call setToNull( col1, 0 ) ! Set the first element of column col1 to null.
col2 = addColumn(tab,"real64",REAL64,units="hm",comment="real64 column")
r64 => real64Data(col2)
do i=0,numberOfRows(tab)-1
r64(i) = 0.25*i
end do
! col is a non-integer column and it would be an
! an error to call setNullValue().
call check( nullable( col2 ) )
call setToNull( col2, 0 ) ! Set the first element of column col2 to null.
if( hasNulls( col2 ) ) then
do i=0,numberOfRows(tab)-1
if( isNull( col2, i ) ) then
write(*,*) "element", i, "is null"
else
write(*,*) "element", i, "is", r64(i)
endif
end do
endif
call release(col1)
call release(col2)
call release(set)
end program example_nullvalues
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! This example show how the numberOfAttributes interface
! is used.
program example_numberofattributes
use dal
implicit none
type(DataSetT) set
type(TableT) tab
set = dataSet("test.dat",CREATE)
call setAttribute(set,"sbool1",.false.,"dataset bool comment")
call setAttribute(set,"sbool2",.false.,"dataset bool comment")
write(*,*) numberOfAttributes( set ) ! 2 attributes
tab = addTable(set,"table",10);
call addAttributes(attributable(tab),attributable(set))
call setAttribute(tab,"sbool3",.false.,"dataset bool comment")
write(*,*) numberOfAttributes( tab ) ! 3 attributes
call release(set)
end program example_numberofattributes
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! This example shows how the numberOfBlocks interface
! is used.
program example_numberofblocks
use dal
implicit none
type(DataSetT) set
type(TableT) tab
type(BlockT) blk
integer i
set = dataSet("test.dat",CREATE)
tab = addTable(set,"table1",10)
tab = addTable(set,"table2",100)
tab = addTable(set,"table3",1000)
write(*,*) numberOfBlocks( set ) ! 3 blocks
! For each block, display the name, and
! add a comment.
do i=0,numberOfBlocks( set ) - 1
blk = block( set, i, MODIFY )
write(*,*) name( blk )
call addComment( blk, "A table comment" )
end do
call release(set)
end program example_numberofblocks
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! This examples shows how the numberOfColumns()
! function is used.
program example_numberofcolumns
use dal
implicit none
type(DataSetT) set
type(TableT) tab
type(ColumnT) col
integer i
set = dataSet("test.dat",CREATE)
tab = addTable(set,"some table",100)
col = addColumn(tab,"bool",BOOLEAN)
col = addColumn(tab,"int8",INTEGER8,units="cm",comment="int8 column")
col = addColumn(tab,"int16",INTEGER16,units="dm",comment="int16 column")
col = addColumn(tab,"int32",INTEGER32,units="m",comment="in32 column")
col = addColumn(tab,"real32",REAL32,units="Dm",comment="real32 column")
col = addColumn(tab,"real64",REAL64,units="hm",comment="real64 column")
col = addColumn(tab,"string",STRING,comment="string column",dimensions=(/80/))
write(*,*) numberOfColumns( tab ) ! 7 columns
! For each column, display the name and
! add an attribute.
do i=0, numberOfColumns( tab ) - 1
col = column( tab, i, MODIFY )
write(*,*) name( col )
call setAttribute( col, "TLMAX", 10, "tlmax attribute" )
end do
call release(set)
end program example_numberofcolumns
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! In this example add dataset is created (opened) containing
! two 3-dimensional arrays, and one table.
!
! It illustrates the use of the numberofdimensions interface.
!
! The second array has the same data type as the first; this
! is ensured by using the arrayDataType() function to determine
! the data type of the first array.
program example_numberofdimensions
use dal
use errorhandling
implicit none
type(DataSetT) set
type(ArrayT) arr
type(TableT) tab
type(ColumnT) col
integer :: i,j
! create a set
set = dataSet("test.dat",CREATE)
arr = addArray(set, "array1", INTEGER32, dimensions=(/3/) )
arr = addArray(set, "array2", dataType( arr ), dimensions=(/3,4/) )
arr = addArray(set, "array3", dataType( arr ), dimensions=(/3,4,5/) )
tab = addTable(set,"table",10)
col = addColumn(tab,"col1",INTEGER8) ! scalar
col = addColumn(tab,"col2",dataType(col),dimensions=(/3/)) ! vector
col = addColumn(tab,"col3",dataType(col),dimensions=(/3,4/)) ! 2-dimensions
col = addColumn(tab,"col4",dataType(col),dimensions=(/3,4,5/)) ! 3-dimensions
col = addColumn(tab,"col5",dataType(col),dimensions=(/3,4,5,6/)) ! 4-dimensions
do i = 0, numberOfBlocks( set ) - 1
! For each block which is an array, display the
! name and number of dimensions.
if( blockType( set, i ).eq.ARRAY_BLOCK ) then
arr = array( set, i, READ )
write(*,*) name( arr ), numberOfDimensions( arr )
else
tab = table( set, i )
do j = 0, numberOfColumns( tab ) - 1
! For each column, display the name
! and the number of dimensions.
col = column( tab, j, READ )
write(*,*) name( col ), numberOfDimensions( col )
end do
end if
end do
call release(set)
end program example_numberofdimensions
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! In this example add dataset is created (opened) containing
! two 3-dimensional arrays, and one table.
!
! It illustrates the use of the numberofelements interface.
!
! The second array has the same data type as the first; this
! is ensured by using the arrayDataType() function to determine
! the data type of the first array.
program example_numberofdimensions
use dal
use errorhandling
implicit none
type(DataSetT) set
type(ArrayT) arr
type(TableT) tab
type(ColumnT) col
integer :: i,j
! create a set
set = dataSet("test.dat",CREATE)
arr = addArray(set, "array1", INTEGER32, dimensions=(/3/) )
arr = addArray(set, "array2", dataType( arr ), dimensions=(/3,4/) )
arr = addArray(set, "array3", dataType( arr ), dimensions=(/3,4,5/) )
tab = addTable(set,"table",10)
col = addColumn(tab,"col1",INTEGER8) ! scalar
col = addColumn(tab,"col2",dataType(col),dimensions=(/3/)) ! vector
col = addColumn(tab,"col3",dataType(col),dimensions=(/3,4/)) ! 2-dimensions
col = addColumn(tab,"col4",dataType(col),dimensions=(/3,4,5/)) ! 3-dimensions
col = addColumn(tab,"col5",dataType(col),dimensions=(/3,4,5,6/)) ! 4-dimensions
do i = 0, numberOfBlocks( set ) - 1
! For each block which is an array, display the
! name, number of dimensions and the number of elements.
if( blockType( set, i ).eq.ARRAY_BLOCK ) then
arr = array( set, i, READ )
write(*,*) name( arr ), numberOfDimensions( arr ), numberOfElements( arr )
else
tab = table( set, i )
do j = 0, numberOfColumns( tab ) - 1
! For each column, display the name,
! number of dimensions and total number of elements.
col = column( tab, j, READ )
write(*,*) name( col ), numberOfDimensions( col ), numberOfRows( col ) * numberOfElements( col )
end do
end if
end do
call release(set)
end program example_numberofdimensions
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! This example shows how the numberOfRows
! interface is used.
program example_numberofrows
use dal
implicit none
type(DataSetT) set
type(TableT) tab
integer i
set = dataSet("test.dat",CREATE)
tab = addTable(set,"table1",10)
tab = addTable(set,"table2",100)
tab = addTable(set,"table3",1000)
do i=0,numberOfBlocks( set ) - 1
tab = table( set, i )
write(*,*) name( tab ), numberOfRows( tab )
end do
call release(set)
end program example_numberofrows
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! This example shows how the parent interface
! is used.
subroutine test1( set, tab, arr, col )
use dal
type(DataSetT), intent(in) :: set
type(TableT), intent(in) :: tab
type(ArrayT), intent(in) :: arr
type(ColumnT), intent(in) :: col
type(AttributeT) att
att = attribute( set,0 )
write(*,*) name( parent( att ))
if( name( parent( att )) /= name( set )) then
call error('internalError',"problem in parent method" )
end if
att = attribute( tab,0 )
write(*,*) name( parent( att ))
if( name( parent( att )) /= name( tab )) then
call error('internalError',"problem in parent method" )
end if
write(*,*) name( parent( tab ))
if( name( parent( tab )) /= name( set )) then
call error('internalError',"problem in parent method" )
end if
att = attribute( arr,0 )
write(*,*) name( parent( att ))
if( name( parent( att )) /= name( arr )) then
call error('internalError',"problem in parent method" )
end if
write(*,*) name( parent( arr ))
if( name( parent( arr )) /= name( set )) then
call error('internalError',"problem in parent method" )
end if
att = attribute( col,0 )
write(*,*) name( parent( att ))
if( name( parent( att )) /= name( col )) then
call error('internalError',"problem in parent method" )
end if
write(*,*) name( parent( col ))
if( name( parent( col )) /= name( tab )) then
call error('internalError',"problem in parent method" )
end if
write(*,*) name( parent( parent( col )))
if( name( parent( parent( col ))) /= name( set )) then
call error('internalError',"problem in parent method" )
end if
end subroutine test1
program example_parent
use dal
implicit none
type(DataSetT) set
type(TableT) tab
type(ColumnT) col
type(ArrayT) arr
integer, dimension(3), parameter :: s = (/ 3,4,2 /)
set = dataSet("test.dat",CREATE)
call setAttribute(set,"sint8",1_int8,"int8 unit","set int8 comment")
tab = addTable(set,"some table",100)
call setAttribute(tab,"sint8",1_int8,"int8 unit","set int8 comment")
arr = addArray(set, "some array", INTEGER32, dimensions=s )
call setAttribute(arr,"sint8",1_int8,"int8 unit","set int8 comment")
col = addColumn(tab,"bool",BOOLEAN)
call setAttribute(col,"TLMIN",1_int8,"int8 unit","set int8 comment")
call test1( set,tab,arr,col )
call release(set)
set = dataSet("test.dat",READ)
tab = table(set,0)
arr = array(set,1,READ)
col = column(tab,0,READ)
call test1( set,tab,arr,col )
call release(set)
end program example_parent
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! This example shows how the qualifiedName
! interface is used.
program example_qualifiedname
use dal
type(DataSetT) :: set
type(ArrayT) :: arr
type(TableT) :: tab
type(ColumnT) :: col
type(AttributeT) :: att
set = dataSet("test.dat",create)
call setAttribute(set,"sbool",.false.,"set bool comment")
arr = addArray(set,"array",integer32, dimensions=(/ 1,2,3 /))
call setAttribute(arr,"abool",.true.,"arr bool comment")
tab = addTable(set,"table",10)
call setAttribute(tab,"tbool",.false.,"tab bool comment")
col = addColumn(tab,"column",INT32,units="UNITS",comment="Column")
call setAttribute(col,"tlmin",1_int32,"int32 unit","col int32 comment")
write(*,*) "qualified data set name: ", qualifiedName( set ) ! test.dat
att = attribute( set, "sbool" )
write(*,*) "qualified data set attribute name: ", qualifiedName( att ) !"test.dat:sbool
write(*,*) "qualified table name: ", qualifiedName( tab )! test.dat:table
att = attribute( tab, "tbool" )
write(*,*) "qualified table attribute name: ", qualifiedName( att ) ! test.dat:table:tbool
write(*,*) "qualified array name: ", qualifiedName( arr ) ! test.dat:array
att = attribute( arr, "abool" )
write(*,*) "qualified array attribute name: ", qualifiedName( att ) ! test.dat:array:abool
write(*,*) "qualified column name: ", qualifiedName( col ) ! test.dat:table:column
att = attribute( col, "tlmin" )
write(*,*) "qualified array attribute name: ", qualifiedName( att ) ! test.dat:table:column:tlmin
call release(set)
end program example_qualifiedname
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! This example shows how to use the real32Array2Data interface.
! In the example a dataset is created (opened) containing
! a table with 2 columns of two 2-dimensional arrays.
!
! The second array has the same data type as the first; this
! is ensured by using the arrayDataType() function to determine
! the data type of the first array.
!
! The columns are then initialised, on a row-by-row
! basis (i.e. accessing the column's data cell-by-cell),
! before the dataset is released (closed).
program example_cellarray2data
use dal
use errorhandling
implicit none
type(DataSetT) set
type(TableT) tab
type(ColumnT) col1, col2
real(kind=SINGLE), dimension(:,:), pointer :: c1, c2
integer, dimension(2), parameter :: s = (/ 3,4 /)
integer :: i,j,k,n
! create a set
set = dataSet("test.dat",CREATE)
tab = addTable(set, "table", 100, "table comment" )
col1 = addColumn( tab, "column1", REAL32, "km", s, "column comment" )
col2 = addColumn( tab, "column2", columnDataType( col1 ), "km", s, "column comment" )
! fill with unique numbers
n = 0
do k=0,numberOfRows(tab) - 1
c1 => real32Array2Data(col1,k)
c2 => real32Array2Data(col2,k)
do j=0,3
do i=0,2
c1(i,j) = n
c2(i,j) = c1(i,j)
n = n + 1
end do
end do
end do
call release(col1)
call release(col2)
call release(set)
end program example_cellarray2data
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! This example shows how to use the real32Array2Data interface.
! In the example a dataset is created (opened) containing
! a table with 2 2-dimensional arrays.
!
! The second array has the same data type as the first; this
! is ensured by using the arrayDataType() function to determine
! the data type of the first array.
!
! The columns are then initialised, on a row-by-row
! basis (i.e. accessing the column's data cell-by-cell),
! before the dataset is released (closed).
program example_arrayarray2data
use dal
use errorhandling
implicit none
type(DataSetT) set
type(TableT) tab
type(ArrayT) arr1, arr2
real(kind=SINGLE), dimension(:,:), pointer :: a1, a2
integer, dimension(2), parameter :: s = (/ 3,4 /)
integer :: i,j,n
! create a set
set = dataSet("test.dat",CREATE)
arr1 = addArray( set, "array1", REAL32, s, "km", "array comment" )
arr2 = addArray( set, "array2", REAL32, s, "km", "array comment" )
! fill with unique numbers
n = 0
a1 => real32Array2Data(arr1)
a2 => real32Array2Data(arr2)
do j=0,3
do i=0,2
a1(i,j) = n
a2(i,j) = a1(i,j)
n = n + 1
end do
end do
call release(arr1)
call release(arr2)
call release(set)
end program example_arrayarray2data
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! In this example add dataset is created (opened) containing
! a table with 2 columns of two 2-dimensional arrays.
!
! The second array has the same data type as the first; this
! is ensured by using the arrayDataType() function to determine
! the data type of the first array.
!
! The columns are then initialised before the
! dataset is released (closed).
program example_array2data
use dal
use errorhandling
implicit none
type(DataSetT) set
type(TableT) tab
type(ColumnT) col1, col2
real(kind=SINGLE), dimension(:,:,:), pointer :: c1, c2
integer, dimension(2), parameter :: s = (/ 3,4 /)
integer :: i,j,k,n
! create a set
set = dataSet("test.dat",CREATE)
tab = addTable(set, "table", 100, "table comment" )
col1 = addColumn( tab, "column1", REAL32, "km", s, "column comment" )
col2 = addColumn( tab, "column2", columnDataType( col1 ), "km", s, "column comment" )
! fill with unique numbers
c1 => real32Array2Data(col1)
c2 => real32Array2Data(col2)
n = 0
do k=0,numberOfRows(tab) - 1
do j=0,3
do i=0,2
c1(i,j,k) = n
c2(i,j,k) = c1(i,j,k)
n = n + 1
end do
end do
end do
call release(col1)
call release(col2)
call release(set)
end program example_array2data
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! In this example add dataset is created (opened) containing
! a table with 2 columns of two 3-dimensional arrays.
!
! The second array has the same data type as the first; this
! is ensured by using the arrayDataType() function to determine
! the data type of the first array.
!
! The columns are then initialised, on a row-by-row
! basis (i.e. accessing the column's data cell-by-cell),
! before the dataset is released (closed).
program example_cellarray3data
use dal
use errorhandling
implicit none
type(DataSetT) set
type(TableT) tab
type(ColumnT) col1, col2
real(kind=SINGLE), dimension(:,:,:), pointer :: c1, c2
integer, dimension(3), parameter :: s = (/ 3,4,5 /)
integer :: i,j,k,l,n
! create a set
set = dataSet("test.dat",CREATE)
tab = addTable(set, "table", 100, "table comment" )
col1 = addColumn( tab, "column1", REAL32, "km", s, "column comment" )
col2 = addColumn( tab, "column2", columnDataType( col1 ), "km", s, "column comment" )
! fill with unique numbers
n = 0
do l=0,numberOfRows(tab) - 1
c1 => real32Array3Data(col1,l)
c2 => real32Array3Data(col2,l)
do k=0,4
do j=0,3
do i=0,2
c1(i,j,k) = n
c2(i,j,k) = c1(i,j,k)
n = n + 1
end do
end do
end do
end do
call release(col1)
call release(col2)
call release(set)
end program example_cellarray3data
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! This example shows how to use the int8Array2Data interface.
! In the example a dataset is created (opened) containing
! a table with 2 3-dimensional arrays.
!
! The second array has the same data type as the first; this
! is ensured by using the arrayDataType() function to determine
! the data type of the first array.
!
! The columns are then initialised, on a row-by-row
! basis (i.e. accessing the column's data cell-by-cell),
! before the dataset is released (closed).
program example_arrayarray3data
use dal
use errorhandling
implicit none
type(DataSetT) set
type(TableT) tab
type(ArrayT) arr1, arr2
real(kind=SINGLE), dimension(:,:,:), pointer :: a1, a2
integer, dimension(3), parameter :: s = (/ 3,4,5 /)
integer :: i,j,k,n
! create a set
set = dataSet("test.dat",CREATE)
arr1 = addArray( set, "array1", REAL32, s, "km", "array comment" )
arr2 = addArray( set, "array2", REAL32, s, "km", "array comment" )
! fill with unique numbers
n = 0
a1 => real32Array3Data(arr1)
a2 => real32Array3Data(arr2)
do k=0,4
do j=0,3
do i=0,2
a1(i,j,k) = n
a2(i,j,k) = a1(i,j,k)
n = n + 1
end do
end do
end do
call release(arr1)
call release(arr2)
call release(set)
end program example_arrayarray3data
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! In this example add dataset is created (opened) containing
! a table with 2 columns of two 3-dimensional arrays.
!
! The second array has the same data type as the first; this
! is ensured by using the arrayDataType() function to determine
! the data type of the first array.
!
! The columns are then initialised before the
! dataset is released (closed).
program example_array3data
use dal
use errorhandling
implicit none
type(DataSetT) set
type(TableT) tab
type(ColumnT) col1, col2
real(kind=SINGLE), dimension(:,:,:,:), pointer :: c1, c2
integer, dimension(3), parameter :: s = (/ 3,4,5 /)
integer :: i,j,k,l,n
! create a set
set = dataSet("test.dat",CREATE)
tab = addTable(set, "table", 100, "table comment" )
col1 = addColumn( tab, "column1", REAL32, "km", s, "column comment" )
col2 = addColumn( tab, "column2", columnDataType( col1 ), "km", s, "column comment" )
! fill with unique numbers
c1 => real32Array3Data(col1)
c2 => real32Array3Data(col1)
n = 0
do l=0,numberOfRows(tab) - 1
do k = 0,4
do j=0,3
do i=0,2
c1(i,j,k,l) = n
c2(i,j,k,l) = c1(i,j,k,l)
n = n + 1
end do
end do
end do
end do
call release(col1)
call release(col2)
call release(set)
end program example_array3data
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! In this example add dataset is created (opened) containing
! a table with 2 columns of two 4-dimensional arrays.
!
! The second array has the same data type as the first; this
! is ensured by using the arrayDataType() function to determine
! the data type of the first array.
!
! The columns are then initialised, on a row-by-row
! basis (i.e. accessing the column's data cell-by-cell),
! before the dataset is released (closed).
program example_cellarray4data
use dal
use errorhandling
implicit none
type(DataSetT) set
type(TableT) tab
type(ColumnT) col1, col2
real(kind=SINGLE), dimension(:,:,:,:), pointer :: c1, c2
integer, dimension(4), parameter :: s = (/ 3,4,5,6 /)
integer :: i,j,k,l,m,n
! create a set
set = dataSet("test.dat",CREATE)
tab = addTable(set, "table", 100, "table comment" )
col1 = addColumn( tab, "column1", REAL32, "km", s, "column comment" )
col2 = addColumn( tab, "column2", columnDataType( col1 ), "km", s, "column comment" )
! fill with unique numbers
n = 0
do m=0,numberOfRows(tab) - 1
c1 => real32Array4Data(col1,m)
c2 => real32Array4Data(col2,m)
do l=0,5
do k=0,4
do j=0,3
do i=0,2
c1(i,j,k,l) = n
c2(i,j,k,l) = c1(i,j,k,l)
n = n + 1
end do
end do
end do
end do
end do
call release(col1)
call release(col2)
call release(set)
end program example_cellarray4data
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! In this example add dataset is created (opened) containing
! a table with 2 columns of two 4-dimensional arrays.
!
! The second array has the same data type as the first; this
! is ensured by using the arrayDataType() function to determine
! the data type of the first array.
!
! The columns are then initialised before the
! dataset is released (closed).
program example_array4data
use dal
use errorhandling
implicit none
type(DataSetT) set
type(TableT) tab
type(ColumnT) col1, col2
real(kind=SINGLE), dimension(:,:,:,:,:), pointer :: c1, c2
integer, dimension(4), parameter :: s = (/ 3,4,5,6 /)
integer :: i,j,k,l,m,n
! create a set
set = dataSet("test.dat",CREATE)
tab = addTable(set, "table", 100, "table comment" )
col1 = addColumn( tab, "column1", REAL32, "km", s, "column comment" )
col2 = addColumn( tab, "column2", columnDataType( col1 ), "km", s, "column comment" )
! fill with unique numbers
c1 => real32Array4Data(col1)
c2 => real32Array4Data(col1)
n = 0
do m=0,numberOfRows(tab) - 1
do l=0,5
do k=0,4
do j=0,3
do i=0,2
c1(i,j,k,l,m) = n
c2(i,j,k,l,m) = c1(i,j,k,l,m)
n = n + 1
end do
end do
end do
end do
end do
call release(col1)
call release(col2)
call release(set)
end program example_array4data
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! This example shows how real32 attributes are used.
! The program creates a dataset containing two real32 attributes,
! together with a table containing two real32 attributes.
! The attributes are then accessed, by name, with
! the real32Attribute() function.
! Also, it is shown how to access the attributes by position.
program example_real32attribute
use dal
use errorhandling
implicit none
type(DataSetT) set
type(TableT) tab
type(AttributeT) att
integer i
set = dataSet("test.dat",CREATE)
call setAttribute(set,"real1",1.0,"real comment")
call setAttribute(set,"real2",2.0,"real comment")
tab = addTable(set,"table",10);
call setAttribute(tab,"real1",3.0,"real comment")
call setAttribute(tab,"real2",4.0,"real comment")
write(*,*) real32Attribute( set, "real1" ) ! output '1.0'
write(*,*) real32Attribute( set, "real2" ) ! output '2.0'
write(*,*) real32Attribute( tab, "real1" ) ! output '3.0'
write(*,*) real32Attribute( tab, "real2" ) ! output '4.0'
do i = 0, numberOfAttributes( set ) - 1
att = attribute( set, i )
write(*,*) real32Attribute( att ) ! output the sequence 1.0, 2.0
end do
call release(set)
end program example_real32attribute
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! In this example add dataset is created (opened) containing
! a table with 2 columns of two 4-dimensional arrays.
!
! The second array has the same data type as the first; this
! is ensured by using the arrayDataType() function to determine
! the data type of the first array.
!
! The columns are then initialised, and then the second column
! is output by accessing the column's data as a flat vector.
program example_real32data
use dal
use errorhandling
implicit none
type(DataSetT) set
type(TableT) tab
type(ColumnT) col1, col2
real(kind=SINGLE), dimension(:,:,:,:,:), pointer :: c1, c2
real(kind=SINGLE), dimension(:), pointer :: cd
integer, dimension(4), parameter :: s = (/ 3,4,5,6 /)
integer :: i,j,k,l,m,n
! create a set
set = dataSet("test.dat",CREATE)
tab = addTable(set, "table", 5, "table comment" )
col1 = addColumn( tab, "column1", REAL32, "km", s, "column comment" )
col2 = addColumn( tab, "column2", columnDataType( col1 ), "km", s, "column comment" )
! fill with unique numbers
c1 => real32Array4Data(col1)
c2 => real32Array4Data(col2)
n = 0
do m=0,numberOfRows(tab) - 1
do l=0,5
do k=0,4
do j=0,3
do i=0,2
c1(i,j,k,l,m) = n
c2(i,j,k,l,m) = c1(i,j,k,l,m)
n = n + 1
end do
end do
end do
end do
end do
call release(col1)
call release(col2)
! Output the col2
cd => real32Data( col2 ) ! Access the column's 4-dimensional data as a flat vector.
do n = 0,numberOfElements(col1) * numberOfRows(tab) - 1
write(*,*) cd(n)
end do
call release(col2)
call release(set)
end program example_real32data
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! In this example add dataset is created (opened) containing
! a table with 2 columns of two vector arrays.
!
! The second array has the same data type as the first; this
! is ensured by using the arrayDataType() function to determine
! the data type of the first array.
!
! The columns are then initialised, on a row-by-row
! basis (i.e. accessing the column's data cell-by-cell),
! before the dataset is released (closed).
program example_cellvectordata
use dal
use errorhandling
implicit none
type(DataSetT) set
type(TableT) tab
type(ColumnT) col1, col2
real(kind=SINGLE), dimension(:), pointer :: c1, c2
integer, dimension(1), parameter :: s = (/ 3 /)
integer :: i,m,n
! create a set
set = dataSet("test.dat",CREATE)
tab = addTable(set, "table", 100, "table comment" )
col1 = addColumn( tab, "column1", REAL32, "km", s, "column comment" )
col2 = addColumn( tab, "column2", columnDataType( col1 ), "km", s, "column comment" )
! fill with unique numbers
n = 0
do m=0,numberOfRows(tab) - 1
c1 => real32VectorData(col1,m)
c2 => real32VectorData(col2,m)
do i=0,2
c1(i) = n
c2(i) = c1(i)
n = n + 1
end do
end do
call release(col1)
call release(col2)
call release(set)
end program example_cellvectordata
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! This example shows how to use the int32Array2Data interface.
! In the example a dataset is created (opened) containing
! a table with 2 vector arrays.
!
! The second array has the same data type as the first; this
! is ensured by using the arrayDataType() function to determine
! the data type of the first array.
!
! The array is then initialised,
program example_arrayvectordata
use dal
use errorhandling
implicit none
type(DataSetT) set
type(TableT) tab
type(ArrayT) arr1, arr2
real(kind=SINGLE), dimension(:), pointer :: a1, a2
integer, dimension(1), parameter :: s = (/ 3 /)
integer :: i,n
! create a set
set = dataSet("test.dat",CREATE)
arr1 = addArray( set, "array1", REAL32, s, "km", "array comment" )
arr2 = addArray( set, "array2", REAL32, s, "km", "array comment" )
! fill with unique numbers
n = 0
a1 => real32VectorData(arr1)
a2 => real32VectorData(arr2)
do i=0,2
a1(i) = n
a2(i) = a1(i)
n = n + 1
end do
call release(arr1)
call release(arr2)
call release(set)
end program example_arrayvectordata
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! In this example add dataset is created (opened) containing
! a table with 2 columns of two vector arrays.
!
! The second column has the same data type as the first; this
! is ensured by using the columnDataType() function to determine
! the data type of the first array.
!
! The columns are then initialised before the
! dataset is released (closed).
program example_columnvectordata
use dal
use errorhandling
implicit none
type(DataSetT) set
type(TableT) tab
type(ColumnT) col1, col2
real(kind=SINGLE), dimension(:,:), pointer :: c1, c2
integer, dimension(1), parameter :: s = (/ 3 /)
integer :: i,m,n
! create a set
set = dataSet("test.dat",CREATE)
tab = addTable(set, "table", 10, "table comment" )
col1 = addColumn( tab, "column1", REAL32, "km", s, "column comment" )
col2 = addColumn( tab, "column2", columnDataType( col1 ), "km", s, "column comment" )
! fill with unique numbers
c1 => real32VectorData(col1)
c2 => real32VectorData(col2)
n = 0
do m=0,numberOfRows(tab) - 1
do i=0,2
c1(i,m) = n
c2(i,m) = c1(i,m)
n = n + 1
end do
end do
call release(col1)
call release(col2)
call release(set)
end program example_columnvectordata
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! This example shows how to use the real64Array2Data interface.
! In the example a dataset is created (opened) containing
! a table with 2 columns of two 2-dimensional arrays.
!
! The second array has the same data type as the first; this
! is ensured by using the arrayDataType() function to determine
! the data type of the first array.
!
! The columns are then initialised, on a row-by-row
! basis (i.e. accessing the column's data cell-by-cell),
! before the dataset is released (closed).
program example_cellarray2data
use dal
use errorhandling
implicit none
type(DataSetT) set
type(TableT) tab
type(ColumnT) col1, col2
real(kind=DOUBLE), dimension(:,:), pointer :: c1, c2
integer, dimension(2), parameter :: s = (/ 3,4 /)
integer :: i,j,k,n
! create a set
set = dataSet("test.dat",CREATE)
tab = addTable(set, "table", 100, "table comment" )
col1 = addColumn( tab, "column1", REAL64, "km", s, "column comment" )
col2 = addColumn( tab, "column2", columnDataType( col1 ), "km", s, "column comment" )
! fill with unique numbers
n = 0
do k=0,numberOfRows(tab) - 1
c1 => real64Array2Data(col1,k)
c2 => real64Array2Data(col2,k)
do j=0,3
do i=0,2
c1(i,j) = n
c2(i,j) = c1(i,j)
n = n + 1
end do
end do
end do
call release(col1)
call release(col2)
call release(set)
end program example_cellarray2data
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! This example shows how to use the real64Array2Data interface.
! In the example a dataset is created (opened) containing
! a table with 2 2-dimensional arrays.
!
! The second array has the same data type as the first; this
! is ensured by using the arrayDataType() function to determine
! the data type of the first array.
!
! The columns are then initialised, on a row-by-row
! basis (i.e. accessing the column's data cell-by-cell),
! before the dataset is released (closed).
program example_arrayarray2data
use dal
use errorhandling
implicit none
type(DataSetT) set
type(TableT) tab
type(ArrayT) arr1, arr2
real(kind=DOUBLE), dimension(:,:), pointer :: a1, a2
integer, dimension(2), parameter :: s = (/ 3,4 /)
integer :: i,j,n
! create a set
set = dataSet("test.dat",CREATE)
arr1 = addArray( set, "array1", REAL64, s, "km", "array comment" )
arr2 = addArray( set, "array2", REAL64, s, "km", "array comment" )
! fill with unique numbers
n = 0
a1 => real64Array2Data(arr1)
a2 => real64Array2Data(arr2)
do j=0,3
do i=0,2
a1(i,j) = n
a2(i,j) = a1(i,j)
n = n + 1
end do
end do
call release(arr1)
call release(arr2)
call release(set)
end program example_arrayarray2data
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! In this example add dataset is created (opened) containing
! a table with 2 columns of two 2-dimensional arrays.
!
! The second array has the same data type as the first; this
! is ensured by using the arrayDataType() function to determine
! the data type of the first array.
!
! The columns are then initialised before the
! dataset is released (closed).
program example_array2data
use dal
use errorhandling
implicit none
type(DataSetT) set
type(TableT) tab
type(ColumnT) col1, col2
real(kind=DOUBLE), dimension(:,:,:), pointer :: c1, c2
integer, dimension(2), parameter :: s = (/ 3,4 /)
integer :: i,j,k,n
! create a set
set = dataSet("test.dat",CREATE)
tab = addTable(set, "table", 100, "table comment" )
col1 = addColumn( tab, "column1", REAL64, "km", s, "column comment" )
col2 = addColumn( tab, "column2", columnDataType( col1 ), "km", s, "column comment" )
! fill with unique numbers
c1 => real64Array2Data(col1)
c2 => real64Array2Data(col2)
n = 0
do k=0,numberOfRows(tab) - 1
do j=0,3
do i=0,2
c1(i,j,k) = n
c2(i,j,k) = c1(i,j,k)
n = n + 1
end do
end do
end do
call release(col1)
call release(col2)
call release(set)
end program example_array2data
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! In this example add dataset is created (opened) containing
! a table with 2 columns of two 3-dimensional arrays.
!
! The second array has the same data type as the first; this
! is ensured by using the arrayDataType() function to determine
! the data type of the first array.
!
! The columns are then initialised, on a row-by-row
! basis (i.e. accessing the column's data cell-by-cell),
! before the dataset is released (closed).
program example_cellarray3data
use dal
use errorhandling
implicit none
type(DataSetT) set
type(TableT) tab
type(ColumnT) col1, col2
real(kind=DOUBLE), dimension(:,:,:), pointer :: c1, c2
integer, dimension(3), parameter :: s = (/ 3,4,5 /)
integer :: i,j,k,l,n
! create a set
set = dataSet("test.dat",CREATE)
tab = addTable(set, "table", 100, "table comment" )
col1 = addColumn( tab, "column1", REAL64, "km", s, "column comment" )
col2 = addColumn( tab, "column2", columnDataType( col1 ), "km", s, "column comment" )
! fill with unique numbers
n = 0
do l=0,numberOfRows(tab) - 1
c1 => real64Array3Data(col1,l)
c2 => real64Array3Data(col2,l)
do k=0,4
do j=0,3
do i=0,2
c1(i,j,k) = n
c2(i,j,k) = c1(i,j,k)
n = n + 1
end do
end do
end do
end do
call release(col1)
call release(col2)
call release(set)
end program example_cellarray3data
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! This example shows how to use the int8Array2Data interface.
! In the example a dataset is created (opened) containing
! a table with 2 3-dimensional arrays.
!
! The second array has the same data type as the first; this
! is ensured by using the arrayDataType() function to determine
! the data type of the first array.
!
! The columns are then initialised, on a row-by-row
! basis (i.e. accessing the column's data cell-by-cell),
! before the dataset is released (closed).
program example_arrayarray3data
use dal
use errorhandling
implicit none
type(DataSetT) set
type(TableT) tab
type(ArrayT) arr1, arr2
real(kind=DOUBLE), dimension(:,:,:), pointer :: a1, a2
integer, dimension(3), parameter :: s = (/ 3,4,5 /)
integer :: i,j,k,n
! create a set
set = dataSet("test.dat",CREATE)
arr1 = addArray( set, "array1", REAL64, s, "km", "array comment" )
arr2 = addArray( set, "array2", REAL64, s, "km", "array comment" )
! fill with unique numbers
n = 0
a1 => real64Array3Data(arr1)
a2 => real64Array3Data(arr2)
do k=0,4
do j=0,3
do i=0,2
a1(i,j,k) = n
a2(i,j,k) = a1(i,j,k)
n = n + 1
end do
end do
end do
call release(arr1)
call release(arr2)
call release(set)
end program example_arrayarray3data
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! In this example add dataset is created (opened) containing
! a table with 2 columns of two 3-dimensional arrays.
!
! The second array has the same data type as the first; this
! is ensured by using the arrayDataType() function to determine
! the data type of the first array.
!
! The columns are then initialised before the
! dataset is released (closed).
program example_array3data
use dal
use errorhandling
implicit none
type(DataSetT) set
type(TableT) tab
type(ColumnT) col1, col2
real(kind=DOUBLE), dimension(:,:,:,:), pointer :: c1, c2
integer, dimension(3), parameter :: s = (/ 3,4,5 /)
integer :: i,j,k,l,n
! create a set
set = dataSet("test.dat",CREATE)
tab = addTable(set, "table", 100, "table comment" )
col1 = addColumn( tab, "column1", REAL64, "km", s, "column comment" )
col2 = addColumn( tab, "column2", columnDataType( col1 ), "km", s, "column comment" )
! fill with unique numbers
c1 => real64Array3Data(col1)
c2 => real64Array3Data(col1)
n = 0
do l=0,numberOfRows(tab) - 1
do k = 0,4
do j=0,3
do i=0,2
c1(i,j,k,l) = n
c2(i,j,k,l) = c1(i,j,k,l)
n = n + 1
end do
end do
end do
end do
call release(col1)
call release(col2)
call release(set)
end program example_array3data
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! In this example add dataset is created (opened) containing
! a table with 2 columns of two 4-dimensional arrays.
!
! The second array has the same data type as the first; this
! is ensured by using the arrayDataType() function to determine
! the data type of the first array.
!
! The columns are then initialised, on a row-by-row
! basis (i.e. accessing the column's data cell-by-cell),
! before the dataset is released (closed).
program example_cellarray4data
use dal
use errorhandling
implicit none
type(DataSetT) set
type(TableT) tab
type(ColumnT) col1, col2
real(kind=DOUBLE), dimension(:,:,:,:), pointer :: c1, c2
integer, dimension(4), parameter :: s = (/ 3,4,5,6 /)
integer :: i,j,k,l,m,n
! create a set
set = dataSet("test.dat",CREATE)
tab = addTable(set, "table", 100, "table comment" )
col1 = addColumn( tab, "column1", REAL64, "km", s, "column comment" )
col2 = addColumn( tab, "column2", columnDataType( col1 ), "km", s, "column comment" )
! fill with unique numbers
n = 0
do m=0,numberOfRows(tab) - 1
c1 => real64Array4Data(col1,m)
c2 => real64Array4Data(col2,m)
do l=0,5
do k=0,4
do j=0,3
do i=0,2
c1(i,j,k,l) = n
c2(i,j,k,l) = c1(i,j,k,l)
n = n + 1
end do
end do
end do
end do
end do
call release(col1)
call release(col2)
call release(set)
end program example_cellarray4data
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! In this example add dataset is created (opened) containing
! a table with 2 columns of two 4-dimensional arrays.
!
! The second array has the same data type as the first; this
! is ensured by using the arrayDataType() function to determine
! the data type of the first array.
!
! The columns are then initialised before the
! dataset is released (closed).
program example_array4data
use dal
use errorhandling
implicit none
type(DataSetT) set
type(TableT) tab
type(ColumnT) col1, col2
real(kind=DOUBLE), dimension(:,:,:,:,:), pointer :: c1, c2
integer, dimension(4), parameter :: s = (/ 3,4,5,6 /)
integer :: i,j,k,l,m,n
! create a set
set = dataSet("test.dat",CREATE)
tab = addTable(set, "table", 100, "table comment" )
col1 = addColumn( tab, "column1", REAL64, "km", s, "column comment" )
col2 = addColumn( tab, "column2", columnDataType( col1 ), "km", s, "column comment" )
! fill with unique numbers
c1 => real64Array4Data(col1)
c2 => real64Array4Data(col1)
n = 0
do m=0,numberOfRows(tab) - 1
do l=0,5
do k=0,4
do j=0,3
do i=0,2
c1(i,j,k,l,m) = n
c2(i,j,k,l,m) = c1(i,j,k,l,m)
n = n + 1
end do
end do
end do
end do
end do
call release(col1)
call release(col2)
call release(set)
end program example_array4data
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! This example shows how real64 attributes are used.
! The program creates a dataset containing two real64 attributes,
! together with a table containing two real64 attributes.
! The attributes are then accessed, by name, with
! the real64Attribute() function.
! Also, it is shown how to access the attributes by position.
program example_real64attribute
use dal
use errorhandling
implicit none
type(DataSetT) set
type(TableT) tab
type(AttributeT) att
integer i
set = dataSet("test.dat",CREATE)
call setAttribute(set,"real1",1.0,"real comment")
call setAttribute(set,"real2",2.0,"real comment")
tab = addTable(set,"table",10);
call setAttribute(tab,"real1",3.0,"real comment")
call setAttribute(tab,"real2",4.0,"real comment")
write(*,*) real64Attribute( set, "real1" ) ! output '1.0'
write(*,*) real64Attribute( set, "real2" ) ! output '2.0'
write(*,*) real64Attribute( tab, "real1" ) ! output '3.0'
write(*,*) real64Attribute( tab, "real2" ) ! output '4.0'
do i = 0, numberOfAttributes( set ) - 1
att = attribute( set, i )
write(*,*) real64Attribute( att ) ! output the sequence 1.0, 2.0
end do
call release(set)
end program example_real64attribute
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! In this example add dataset is created (opened) containing
! a table with 2 columns of two 4-dimensional arrays.
!
! The second array has the same data type as the first; this
! is ensured by using the arrayDataType() function to determine
! the data type of the first array.
!
! The columns are then initialised, and then the second column
! is output by accessing the column's data as a flat vector.
program example_real64data
use dal
use errorhandling
implicit none
type(DataSetT) set
type(TableT) tab
type(ColumnT) col1, col2
real(kind=DOUBLE), dimension(:,:,:,:,:), pointer :: c1, c2
real(kind=DOUBLE), dimension(:), pointer :: cd
integer, dimension(4), parameter :: s = (/ 3,4,5,6 /)
integer :: i,j,k,l,m,n
! create a set
set = dataSet("test.dat",CREATE)
tab = addTable(set, "table", 5, "table comment" )
col1 = addColumn( tab, "column1", REAL64, "km", s, "column comment" )
col2 = addColumn( tab, "column2", columnDataType( col1 ), "km", s, "column comment" )
! fill with unique numbers
c1 => real64Array4Data(col1)
c2 => real64Array4Data(col2)
n = 0
do m=0,numberOfRows(tab) - 1
do l=0,5
do k=0,4
do j=0,3
do i=0,2
c1(i,j,k,l,m) = n
c2(i,j,k,l,m) = c1(i,j,k,l,m)
n = n + 1
end do
end do
end do
end do
end do
call release(col1)
call release(col2)
! Output the col2
cd => real64Data( col2 ) ! Access the column's 4-dimensional data as a flat vector.
do n = 0,numberOfElements(col1) * numberOfRows(tab) - 1
write(*,*) cd(n)
end do
call release(col2)
call release(set)
end program example_real64data
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! In this example add dataset is created (opened) containing
! a table with 2 columns of two vector arrays.
!
! The second array has the same data type as the first; this
! is ensured by using the arrayDataType() function to determine
! the data type of the first array.
!
! The columns are then initialised, on a row-by-row
! basis (i.e. accessing the column's data cell-by-cell),
! before the dataset is released (closed).
program example_cellvectordata
use dal
use errorhandling
implicit none
type(DataSetT) set
type(TableT) tab
type(ColumnT) col1, col2
real(kind=DOUBLE), dimension(:), pointer :: c1, c2
integer, dimension(1), parameter :: s = (/ 3 /)
integer :: i,m,n
! create a set
set = dataSet("test.dat",CREATE)
tab = addTable(set, "table", 100, "table comment" )
col1 = addColumn( tab, "column1", REAL64, "km", s, "column comment" )
col2 = addColumn( tab, "column2", columnDataType( col1 ), "km", s, "column comment" )
! fill with unique numbers
n = 0
do m=0,numberOfRows(tab) - 1
c1 => real64VectorData(col1,m)
c2 => real64VectorData(col2,m)
do i=0,2
c1(i) = n
c2(i) = c1(i)
n = n + 1
end do
end do
call release(col1)
call release(col2)
call release(set)
end program example_cellvectordata
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! This example shows how to use the int64Array2Data interface.
! In the example a dataset is created (opened) containing
! a table with 2 vector arrays.
!
! The second array has the same data type as the first; this
! is ensured by using the arrayDataType() function to determine
! the data type of the first array.
!
! The array is then initialised,
program example_arrayvectordata
use dal
use errorhandling
implicit none
type(DataSetT) set
type(TableT) tab
type(ArrayT) arr1, arr2
real(kind=DOUBLE), dimension(:), pointer :: a1, a2
integer, dimension(1), parameter :: s = (/ 3 /)
integer :: i,n
! create a set
set = dataSet("test.dat",CREATE)
arr1 = addArray( set, "array1", REAL64, s, "km", "array comment" )
arr2 = addArray( set, "array2", REAL64, s, "km", "array comment" )
! fill with unique numbers
n = 0
a1 => real64VectorData(arr1)
a2 => real64VectorData(arr2)
do i=0,2
a1(i) = n
a2(i) = a1(i)
n = n + 1
end do
call release(arr1)
call release(arr2)
call release(set)
end program example_arrayvectordata
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! In this example add dataset is created (opened) containing
! a table with 2 columns of two vector arrays.
!
! The second column has the same data type as the first; this
! is ensured by using the columnDataType() function to determine
! the data type of the first array.
!
! The columns are then initialised before the
! dataset is released (closed).
program example_columnvectordata
use dal
use errorhandling
implicit none
type(DataSetT) set
type(TableT) tab
type(ColumnT) col1, col2
real(kind=DOUBLE), dimension(:,:), pointer :: c1, c2
integer, dimension(1), parameter :: s = (/ 3 /)
integer :: i,m,n
! create a set
set = dataSet("test.dat",CREATE)
tab = addTable(set, "table", 10, "table comment" )
col1 = addColumn( tab, "column1", REAL64, "km", s, "column comment" )
col2 = addColumn( tab, "column2", columnDataType( col1 ), "km", s, "column comment" )
! fill with unique numbers
c1 => real64VectorData(col1)
c2 => real64VectorData(col2)
n = 0
do m=0,numberOfRows(tab) - 1
do i=0,2
c1(i,m) = n
c2(i,m) = c1(i,m)
n = n + 1
end do
end do
call release(col1)
call release(col2)
call release(set)
end program example_columnvectordata
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! This example shows how the label, relabel, name and rename interfaces are used.
subroutine displayLabelled( l )
use dal
implicit none
type(LabelledT), intent(in) :: l
write(*,*) "the object with name ", name( l ), " has label: ", label(l)
end subroutine displayLabelled
subroutine display( set )
use dal
implicit none
type(DataSetT) set
type(ArrayT) arr
type(TableT) tab
type(ColumnT) col
type(AttributeT) att
att = attribute( set, 0 )
write(*,*) name(att), label( att )
call displayLabelled( labelled( att ) )
arr = array( set, 0, READ )
write(*,*) name(arr), label( arr )
call displayLabelled( labelled( arr ) )
att = attribute( arr, 0 )
write(*,*) name(att), label( att )
call displayLabelled( labelled( att ) )
tab = table( set, 1 )
write(*,*) name(tab), label( tab )
call displayLabelled( labelled( tab ) )
att = attribute( tab, 0 )
write(*,*) name(att), label( att )
call displayLabelled( labelled( att ) )
col = column( tab, 0, READ )
write(*,*) name(col), label( col )
call displayLabelled( labelled( col ) )
att = attribute( col, 0 )
write(*,*) name(att), label( att )
call displayLabelled( labelled( att ) )
end subroutine display
program example_labelled
use dal
implicit none
type(DataSetT) set
type(ArrayT) arr
type(TableT) tab
type(ColumnT) col
! type(AttributeT) att
! integer(kind=int32), dimension(:,:,:), pointer :: a
integer, dimension(3), parameter :: s = (/ 3,4,2 /)
! create a set
set = dataSet("test.dat",CREATE)
call setAttribute(set,"att1","value1","a dataset attribute comment")
arr = addArray(set, "array", INTEGER32, comment="an array comment", dimensions=s )
call setAttribute(arr,"att2","value2","an array attribute comment")
tab = addTable(set, "table", 10, comment="a table comment" )
call setAttribute(tab,"att3","value3","a table attribute comment")
col = addColumn(tab,"int8",INTEGER8,comment="a column comment")
call setAttribute(col,"TLMAX","value4","a column attribute comment")
call display( set )
call relabel( tab, "a new table comment" )
call rename( col, "newcolnm" )
call display( set )
call release( set )
end program example_labelled
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! This example shows how the label, relabel, name and rename interfaces are used.
subroutine displayLabelled( l )
use dal
implicit none
type(LabelledT), intent(in) :: l
write(*,*) "the object with name ", name( l ), " has label: ", label(l)
end subroutine displayLabelled
subroutine display( set )
use dal
implicit none
type(DataSetT) set
type(ArrayT) arr
type(TableT) tab
type(ColumnT) col
type(AttributeT) att
att = attribute( set, 0 )
write(*,*) name(att), label( att )
call displayLabelled( labelled( att ) )
arr = array( set, 0, READ )
write(*,*) name(arr), label( arr )
call displayLabelled( labelled( arr ) )
att = attribute( arr, 0 )
write(*,*) name(att), label( att )
call displayLabelled( labelled( att ) )
tab = table( set, 1 )
write(*,*) name(tab), label( tab )
call displayLabelled( labelled( tab ) )
att = attribute( tab, 0 )
write(*,*) name(att), label( att )
call displayLabelled( labelled( att ) )
col = column( tab, 0, READ )
write(*,*) name(col), label( col )
call displayLabelled( labelled( col ) )
att = attribute( col, 0 )
write(*,*) name(att), label( att )
call displayLabelled( labelled( att ) )
end subroutine display
program example_labelled
use dal
implicit none
type(DataSetT) set
type(ArrayT) arr
type(TableT) tab
type(ColumnT) col
! type(AttributeT) att
! integer(kind=int32), dimension(:,:,:), pointer :: a
integer, dimension(3), parameter :: s = (/ 3,4,2 /)
! create a set
set = dataSet("test.dat",CREATE)
call setAttribute(set,"att1","value1","a dataset attribute comment")
arr = addArray(set, "array", INTEGER32, comment="an array comment", dimensions=s )
call setAttribute(arr,"att2","value2","an array attribute comment")
tab = addTable(set, "table", 10, comment="a table comment" )
call setAttribute(tab,"att3","value3","a table attribute comment")
col = addColumn(tab,"int8",INTEGER8,comment="a column comment")
call setAttribute(col,"TLMAX","value4","a column attribute comment")
call display( set )
call relabel( tab, "a new table comment" )
call rename( col, "newcolnm" )
call display( set )
call release( set )
end program example_labelled
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! This example shows how the setAttribute
! interface is used.
program example_setattribute
use dal
implicit none
type(DataSetT) set
set = dataSet("test.dat",CREATE)
call setAttribute(set,"test1","some value","some comment to the attribute")
call setAttribute(set,"TELESCOP","XMM","Telescope (mission) name")
write(*,*) numberOfAttributes( set ) ! 2 attributes
call release(set)
end program example_setattribute
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! This example shows how the setAttributes interface
! is used.
program example_setattributes
use dal
use errorhandling
implicit none
type(DataSetT) set
type(TableT) tab
set = dataSet("test.dat",CREATE)
call setAttribute(set,"sbool1",.false.,"dataset bool comment")
call setAttribute(set,"sbool2",.false.,"dataset bool comment")
tab = addTable(set,"table",10);
call setAttributes(attributable(tab),attributable(set))
write(*,*) numberOfAttributes( tab ) ! 2 attributes
call release(set)
end program example_setattributes
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! This example shows how to set the data in
! a variable length column.
program example_setdata
use dal
implicit none
integer, parameter :: nRows = 10
integer, parameter :: maxCellSize = 100
integer, dimension(0) :: zeroSize
integer(kind=INT32) :: i
type(DataSetT) :: set
type(TableT) :: tab
type(ColumnT) :: i8col1, i8col2, i16col1, i16col2, i32col1, i32col2
type(ColumnT) :: r32col1, r32col2, r64col1, r64col2
type(ColumnT) :: scol1, scol2, bcol1, bcol2
logical(kind=bool), dimension(maxCellSize) :: b
integer(kind=INT8), dimension(maxCellSize) :: i8
integer(kind=INT16), dimension(maxCellSize) :: i16
integer(kind=INT32), dimension(maxCellSize) :: i32
real(kind=SINGLE), dimension(maxCellSize) :: r32
real(kind=DOUBLE), dimension(maxCellSize) :: r64
character(len=maxCellSize) :: s
real(kind=SINGLE), dimension(:), pointer :: r32Data
s = "ABCDEFGHIJKLMNOPQRSTUVWXYZ"
do i = 1, maxCellSize
i8(i) = i
i16(i) = i
i32(i) = i
r32(i) = i
r64(i) = i
b(i) = ((i / 2).eq.0 )
end do
set = dataSet("test.dat",Create)
tab = addTable(set,"someTable",nRows)
bcol1 = addColumn(tab,"bcol1",Boolean, &
dimensions=zeroSize,comment="bool data")
bcol2 = addColumn(tab,"bcol2",Boolean, &
dimensions=zeroSize,comment="bool data")
i8col1 = addColumn(tab,"i8col1",Integer8,units="m", &
dimensions=zeroSize,comment="int8 data")
i8col2 = addColumn(tab,"i8col2",Integer8,units="m", &
dimensions=zeroSize,comment="int8 data")
i16col1 = addColumn(tab,"i16col1",Integer16,units="m", &
dimensions=zeroSize,comment="int16 data")
i16col2 = addColumn(tab,"i16col2",Integer16,units="m", &
dimensions=zeroSize,comment="int16 data")
i32col1 = addColumn(tab,"i32col1",Integer32,units="m", &
dimensions=zeroSize,comment="int32 data")
i32col2 = addColumn(tab,"i32col2",Integer32,units="m", &
dimensions=zeroSize,comment="int32 data")
r32col1 = addColumn(tab,"r32col1",Real32,units="m", &
dimensions=zeroSize,comment="real32 data")
r32col2 = addColumn(tab,"r32col2",Real32,units="m", &
dimensions=zeroSize,comment="real32 data")
r64col1 = addColumn(tab,"r64col1",Real64,units="m", &
dimensions=zeroSize,comment="real64 data")
r64col2 = addColumn(tab,"r64col2",Real64,units="m", &
dimensions=zeroSize,comment="real64 data")
scol1 = addColumn(tab,"scol1",String,units="m", &
dimensions=zeroSize,comment="string data")
scol2 = addColumn(tab,"scol2",String, &
dimensions=zeroSize,comment="string data")
do i=0,nRows - 1
call setData( bcol1, i, b( 1 : i + 1 ))
call setData( bcol2, i, b( 1 : nRows - i ))
call setData( i8col1, i, i8( 1 : i + 1 ))
call setData( i8col2, i, i8( 1 : nRows - i ))
call setData( i16col1, i, i16( 1 : i + 1 ))
call setData( i16col2, i, i16( 1 : nRows - i ))
call setData( i32col1, i, i32( 1 : i + 1 ))
call setData( i32col2, i, i32( 1 : nRows - i ))
call setData( r32col1, i, r32( 1 : i + 1 ))
call setData( r32col2, i, r32( 1 : nRows - i ))
call setData( r64col1, i, r64( 1 : i + 1 ))
call setData( r64col2, i, r64( 1 : nRows - i ))
call setData( scol1, i, s( 1 : i + 1 ))
call setData( scol2, i, s( 1 : nRows - i ))
end do
call release( set )
set = dataSet("test.dat",Modify)
tab = table(set,"someTable")
bcol1 = column(tab,"bcol1",Read)
bcol2 = column(tab,"bcol2",Read)
i8col1 = column(tab,"i8col1",Read)
i8col2 = column(tab,"i8col2",Read)
i16col1 = column(tab,"i16col1",Read)
i16col2 = column(tab,"i16col2",Read)
i32col1 = column(tab,"i32col1",Read)
i32col2 = column(tab,"i32col2",Read)
r32col1 = column(tab,"r32col1",Read)
r32col2 = column(tab,"r32col2",Read)
r64col1 = column(tab,"r64col1",Read)
r64col2 = column(tab,"r64col2",Read)
scol1 = column(tab,"scol1",Read)
scol2 = column(tab,"scol2",Read)
do i = 0, nRows - 1
write(*,*) boolData( bcol1, i )
write(*,*) boolData( bcol2, i )
write(*,*) int8Data( i8col1, i )
write(*,*) int8Data( i8col2, i )
write(*,*) int16Data( i16col1, i )
write(*,*) int16Data( i16col2, i )
write(*,*) int32Data( i32col1, i )
write(*,*) int32Data( i32col2, i )
write(*,*) real32Data( r32col1, i )
write(*,*) real32Data( r32col2, i )
write(*,*) real64Data( r64col1, i )
write(*,*) real64Data( r64col2, i )
write(*,*) stringCell( scol1, i )
write(*,*) stringCell( scol2, i )
end do
call release( set )
end program example_setdata
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! This example shows how the setexists()
! function is used.
program example_setexists
use dal
implicit none
type(DataSetT) set
set = dataSet("test.dat",CREATE)
call release(set)
if( setExists( "test.dat" ) ) then
write(*,*) 'Very strange'
end if
end program example_setexists
The null value of an object containing integer data (if it has been defined) may be obtained with the function intNullValue().
The logical function nullDefined() may be used to determine if the null value has been defined.
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! This example shows how null values are used.
subroutine check( thisNullable )
use dal
type(NullableT), intent(in) :: thisNullable
write(*,*) "Null defined?: ", nullDefined( thisNullable ), nullType( thisNullable )
end subroutine check
program example_nullvalues
use dal
use errorhandling
implicit none
type(DataSetT) set
type(ArrayT) arr1, arr2
type(TableT) tab
type(ColumnT) col1, col2
integer(kind=int32), dimension(:), pointer :: i32
real(kind=double), dimension(:), pointer :: r64
integer(kind=int32), dimension(:,:,:), pointer :: a1, a2
integer, dimension(3), parameter :: s = (/ 3,4,2 /)
integer :: i,j,k,n
! create a set
set = dataSet("test.dat",CREATE)
arr1 = addArray(set, "array1", INTEGER32, dimensions=s )
arr2 = addArray(set, "array2", arrayDataType( arr1 ), dimensions=s )
! fill with unique numbers
a1 => int32Array3Data(arr1)
a2 => int32Array3Data(arr1)
n = 0
do k=0,1
do j=0,3
do i=0,2
a1(i,j,k) = n
a2(i,j,k) = a1(i,j,k) + 1
n = n + 1
end do
end do
end do
call setNullValue( arr1, 999999 )
call check( nullable( arr1 ) )
call setToNull( arr1, 0 ) ! Set the first element of array arr1 to null.
! Would have given an error, if the null
! value of array arr1 had not been set.
if( nullType( arr1 ) .eq. INTEGER_NULL ) then !
write(*,*) "Using null value of arr1, in arr2"
call setNullValue( arr2, intNullValue( arr1 ))
else
call setNullValue( arr2, 999999 )
end if
call check( nullable( arr2 ) )
call setToNull( arr2, 1 ) ! Set the second element of array arr2 to null.
! Would have given an error, if the null
! value of array arr2 had not been set.
call release(arr1)
call release(arr2)
tab = addTable(set,"some table",100)
col1 = addColumn(tab,"int32",INTEGER32,units="m",comment="in32 column")
i32 => int32Data(col1)
do i=0,numberOfRows(tab)-1
i32(i) = 3*i
end do
call setNullValue( col1, 999999 )
call check( nullable( col1 ) )
call setToNull( col1, 0 ) ! Set the first element of column col1 to null.
col2 = addColumn(tab,"real64",REAL64,units="hm",comment="real64 column")
r64 => real64Data(col2)
do i=0,numberOfRows(tab)-1
r64(i) = 0.25*i
end do
! col is a non-integer column and it would be an
! an error to call setNullValue().
call check( nullable( col2 ) )
call setToNull( col2, 0 ) ! Set the first element of column col2 to null.
if( hasNulls( col2 ) ) then
do i=0,numberOfRows(tab)-1
if( isNull( col2, i ) ) then
write(*,*) "element", i, "is null"
else
write(*,*) "element", i, "is", r64(i)
endif
end do
endif
call release(col1)
call release(col2)
call release(set)
end program example_nullvalues
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! This example shows how the setStringCell()
! function is used.
program example_setstringcell
use dal
implicit none
type(DataSetT) set
type(TableT) tab
type(ColumnT) col
character(len=12) :: s
integer i
s = "abcdef"
set = dataSet("test.dat",CREATE)
tab = addTable(set,"some table",100)
col = addColumn(tab,"string",STRING,comment="string column",dimensions=(/80/))
do i=0,numberOfRows(tab)-1
write(s,'(A6,I2)') "string",i
call setStringCell(col,i,s)
write(*,*) stringCell( col, i )
end do
call release(set)
end program example_setstringcell
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! This example shows how null values are used.
subroutine check( thisNullable )
use dal
type(NullableT), intent(in) :: thisNullable
write(*,*) "Null defined?: ", nullDefined( thisNullable ), nullType( thisNullable )
end subroutine check
program example_nullvalues
use dal
use errorhandling
implicit none
type(DataSetT) set
type(ArrayT) arr1, arr2
type(TableT) tab
type(ColumnT) col1, col2
integer(kind=int32), dimension(:), pointer :: i32
real(kind=double), dimension(:), pointer :: r64
integer(kind=int32), dimension(:,:,:), pointer :: a1, a2
integer, dimension(3), parameter :: s = (/ 3,4,2 /)
integer :: i,j,k,n
! create a set
set = dataSet("test.dat",CREATE)
arr1 = addArray(set, "array1", INTEGER32, dimensions=s )
arr2 = addArray(set, "array2", arrayDataType( arr1 ), dimensions=s )
! fill with unique numbers
a1 => int32Array3Data(arr1)
a2 => int32Array3Data(arr1)
n = 0
do k=0,1
do j=0,3
do i=0,2
a1(i,j,k) = n
a2(i,j,k) = a1(i,j,k) + 1
n = n + 1
end do
end do
end do
call setNullValue( arr1, 999999 )
call check( nullable( arr1 ) )
call setToNull( arr1, 0 ) ! Set the first element of array arr1 to null.
! Would have given an error, if the null
! value of array arr1 had not been set.
if( nullType( arr1 ) .eq. INTEGER_NULL ) then !
write(*,*) "Using null value of arr1, in arr2"
call setNullValue( arr2, intNullValue( arr1 ))
else
call setNullValue( arr2, 999999 )
end if
call check( nullable( arr2 ) )
call setToNull( arr2, 1 ) ! Set the second element of array arr2 to null.
! Would have given an error, if the null
! value of array arr2 had not been set.
call release(arr1)
call release(arr2)
tab = addTable(set,"some table",100)
col1 = addColumn(tab,"int32",INTEGER32,units="m",comment="in32 column")
i32 => int32Data(col1)
do i=0,numberOfRows(tab)-1
i32(i) = 3*i
end do
call setNullValue( col1, 999999 )
call check( nullable( col1 ) )
call setToNull( col1, 0 ) ! Set the first element of column col1 to null.
col2 = addColumn(tab,"real64",REAL64,units="hm",comment="real64 column")
r64 => real64Data(col2)
do i=0,numberOfRows(tab)-1
r64(i) = 0.25*i
end do
! col is a non-integer column and it would be an
! an error to call setNullValue().
call check( nullable( col2 ) )
call setToNull( col2, 0 ) ! Set the first element of column col2 to null.
if( hasNulls( col2 ) ) then
do i=0,numberOfRows(tab)-1
if( isNull( col2, i ) ) then
write(*,*) "element", i, "is null"
else
write(*,*) "element", i, "is", r64(i)
endif
end do
endif
call release(col1)
call release(col2)
call release(set)
end program example_nullvalues
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! This example shows how the setUnits interface
! is used.
program example_setunits
use dal
implicit none
type(DataSetT) set
type(TableT) tab
type(ColumnT) col
set = dataSet("test.dat",CREATE)
tab = addTable(set,"some table",100)
col = addColumn(tab,"int8",INTEGER8,units="cm",comment="int8 column")
call release(set)
set = dataSet("test.dat",MODIFY)
tab = table( set, 0 )
col = column( tab, 0, MODIFY )
write(*,*) units( col )
call setUnits( col, "mm" )
write(*,*) units( col )
call release(set)
end program example_setunits
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! This example shows how string attributes are used.
! The program creates a dataset containing two string attributes,
! together with a table containing two string attributes.
! The attributes are then accessed, by name, with
! the stringAttribute() function.
! Also, it is shown how to access the attributes by position.
program example_stringattribute
use dal
use errorhandling
implicit none
type(DataSetT) set
type(TableT) tab
type(AttributeT) att
integer i
set = dataSet("test.dat",CREATE)
call setAttribute(set,"string1","abcdef","string comment")
call setAttribute(set,"string2","ghijkl","string comment")
tab = addTable(set,"table",10);
call setAttribute(tab,"string1","abcdef","string comment")
call setAttribute(tab,"string2","ghijkl","string comment")
write(*,*) stringAttribute( set, "string1" ) ! output 'abcdef
write(*,*) stringAttribute( set, "string2" ) ! output 'ghijkl'
write(*,*) stringAttribute( tab, "string1" ) ! output 'abcdef
write(*,*) stringAttribute( tab, "string2" ) ! output 'ghijkl'
do i = 0, numberOfAttributes( set ) - 1
att = attribute( set, i )
write(*,*) stringAttribute( att ) ! output the sequence 'abcdef', 'ghijkl'
end do
call release(set)
end program example_stringattribute
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! This example shows how the stringCell()
! function is used.
program example_stringcell
use dal
implicit none
type(DataSetT) set
type(TableT) tab
type(ColumnT) col
character(len=12) :: s
integer i
s = "abcdef"
set = dataSet("test.dat",CREATE)
tab = addTable(set,"some table",100)
col = addColumn(tab,"string",STRING,comment="string column",dimensions=(/12/))
do i=0,numberOfRows(tab)-1
write(s,'(A6,I2)') "string",i
call setStringCell(col,i,s)
write(*,*) stringCell( col, i )
end do
call release(set)
end program example_stringcell
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
! This example shows how the table
! interface is used.
program example_table
use dal
implicit none
type(DataSetT) set
type(TableT) tab
integer i
set = dataSet("test.dat",CREATE)
tab = addTable(set,"table1",10)
tab = addTable(set,"table2",100)
tab = addTable(set,"table3",1000)
do i=0,numberOfBlocks( set ) - 1
tab = table( set, i ) ! Access table by number
write(*,*) name( tab )
end do
tab = table( set, "table1" ) ! Access table by name
write(*,*) name( tab )
call release(set)
end program example_table
! ESA (C) 2000-2018
!
! This file is part of ESA's XMM-Newton Scientific Analysis System (SAS).
!
! SAS is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! SAS is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with SAS. If not, see <http://www.gnu.org/licenses/>.
program example_columnunits
use dal
implicit none
type(DataSetT) set
type(TableT) tab
type(ColumnT) col
integer i, coltype
set = dataSet("test.dat",CREATE)
tab = addTable(set,"some table",100)
col = addColumn(tab,"bool",BOOLEAN)
col = addColumn(tab,"int8",INTEGER8,units="cm",comment="int8 column")
col = addColumn(tab,"int16",INTEGER16,units="dm",comment="int16 column")
col = addColumn(tab,"int32",INTEGER32,units="m",comment="in32 column")
col = addColumn(tab,"real32",REAL32,units="Dm",comment="real32 column")
col = addColumn(tab,"real64",REAL64,units="hm",comment="real64 column")
col = addColumn(tab,"string",STRING,comment="string column",dimensions=(/80/))
do i=0, numberOfColumns( tab ) - 1
col = column( tab, i, READ )
coltype = columnDataType( col )
if(coltype.eq.INTEGER8.or.coltype.eq.INTEGER16.or.coltype.eq.INTEGER32 &
.or.coltype.eq.REAL32.or.coltype.eq.REAL64) then
write(*,*) units( col )
end if
end do
call release(set)
end program example_columnunits
! Extended DAL
subroutine subTableSeek( table, from, count ) type(SubTableT), intent(in) :: table integer, intent(in) :: from, count
call error( "", errorMessage )
end subroutine
end module Dal
XMM-Newton SOC -- 2025-01-27