Loading...
Searching...
No Matches
columnset.f90
1
4module odbc_columnset
5 use, intrinsic :: iso_c_binding
6 use odbc_constants
7 use sql, only: sqlbindcol
8
9 implicit none; private
10
14 type, public :: column
15 character(:, c_char), allocatable :: name
16 integer(SQLSMALLINT) :: type
17 integer(SQLULEN) :: size
18 integer(SQLSMALLINT) :: decim_size
19 integer(SQLSMALLINT) :: nullable !0: NOT-NULL,1: NULL,2: NOT-KNOWN
20 character(:), allocatable :: content
21 end type
22
27 type, public :: columnset
28 private
29 integer :: ncols = 0
30 type(column), allocatable, public :: items(:)
31 contains
32 private
33 procedure, pass(this), public :: add => columnset_add_column
34 procedure, pass(this), public :: addrange => columnset_addrange_columns
35 procedure, pass(this), public :: bind => columnset_bind
36 procedure, pass(this), public :: count => columnset_get_columns_count
37 procedure, pass(this), private :: columnset_get_column_from_id
38 procedure, pass(this), private :: columnset_get_column_from_name
39 generic, public :: get => columnset_get_column_from_id, &
40 columnset_get_column_from_name
41 final :: columnset_finalize
42 end type
43
44contains
45
52 function columnset_bind(this, stmt, col_no) result(res)
53 class(columnset), intent(inout) :: this
54 type(sqlhstmt), intent(inout) :: stmt
55 integer, intent(in) :: col_no
56 !private
57 integer(SQLRETURN) :: res
58
59 res = columnset_bind_internal(stmt, int(col_no, sqlusmallint), this%items(col_no)%content)
60 contains
61 function columnset_bind_internal(stmt, col_no, buff) result(res)
62 type(sqlhstmt), intent(inout) :: stmt
63 integer(SQLUSMALLINT), intent(in) :: col_no
64 character(*, SQLCHAR), intent(inout), target :: buff
65 !private
66 integer(SQLLEN), allocatable :: sz
67 integer(SQLRETURN) :: res
68
69 allocate(sz, source = 0)
70 buff = ''
71 res = sqlbindcol(stmt, col_no, sql_char, c_loc(buff), &
72 len(buff, c_long), sz)
73 end function
74 end function
75
79 function columnset_get_columns_count(this) result(res)
80 class(columnset), intent(in) :: this
81 integer :: res
82 res = this%ncols
83 end function
84
88 subroutine columnset_add_column(this, col)
89 class(columnset), intent(inout) :: this
90 type(column), intent(in) :: col
91 !private
92 type(column), allocatable :: tmp(:)
93
94 if (.not. allocated(this%items)) allocate(this%items(0))
95 this%ncols = this%ncols + 1
96 allocate(tmp(this%ncols))
97 tmp(:this%ncols-1) = this%items
98 tmp(this%ncols) = col
99 call move_alloc(tmp, this%items)
100 end subroutine
101
105 subroutine columnset_addrange_columns(this, cols)
106 class(columnset), intent(inout) :: this
107 type(column), intent(in) :: cols(:)
108 !private
109 type(column), allocatable :: tmp(:)
110
111 if (.not. allocated(this%items)) allocate(this%items(0))
112 this%ncols = this%ncols + size(cols)
113 allocate(tmp(this%ncols))
114 tmp(:this%ncols-size(cols)) = this%items
115 tmp(this%ncols-size(cols)+1:) = cols
116 call move_alloc(tmp, this%items)
117 end subroutine
118
124 function columnset_get_column_from_id(this, n) result(res)
125 class(columnset), intent(inout), target :: this
126 integer, intent(in) :: n
127 type(column), pointer :: res
128
129 if (size(this%items) <= 0) then
130 res => null()
131 return
132 end if
133
134 res => this%items(n)
135 end function
136
141 function columnset_get_column_from_name(this, name) result(res)
142 class(columnset), intent(inout), target :: this
143 character(*), intent(in) :: name
144 type(column), pointer :: res
145 !private
146 integer :: i, sz
147
148 sz = size(this%items)
149 do i = 1, sz
150 res => this%items(i)
151 if (trim(res%name) == trim(adjustl(name))) then
152 return
153 end if
154 res => null()
155 end do
156 end function
157
158 subroutine columnset_finalize(this)
159 type(columnset), intent(inout) :: this
160
161 if (allocated(this%items)) deallocate (this%items)
162 end subroutine
163
164end module
integer(sqlreturn) function columnset_bind(this, stmt, col_no)
Binds a odbc_columnset::column to an ODBC statement handle for data retrieval, using SQL_CHAR binding...
Definition columnset.f90:53
Triming of c-string returning fortran allocatable characters.
Represents metadata and data for a single column in a query result, storing name, type,...
Definition columnset.f90:14
Manages a collection of odbc_columnset::column objects in a query result set, providing methods to ad...
Definition columnset.f90:27