Skip to content

Commit 814f657

Browse files
committed
Completed tutorial
1. added all three parts 2. corrected typos
1 parent ff55891 commit 814f657

File tree

1 file changed

+196
-17
lines changed

1 file changed

+196
-17
lines changed

learn/quickstart/derived_types.md

Lines changed: 196 additions & 17 deletions
Original file line numberDiff line numberDiff line change
@@ -4,9 +4,9 @@ title: Derived types
44
permalink: /learn/quickstart/derived_types
55
---
66

7-
As discussed previously in [Variables]({{site.baseurl}}/learn/quickstart/variables) there are five built-in data types in Fortran. _Derived types_ is a special form of data type that can encapsulate other built-in types as well as other _derived types_. It could be considered as the equivalent of _struct_ in the C/C++ programming languages.
7+
As discussed previously in [Variables]({{site.baseurl}}/learn/quickstart/variables) there are five built-in data types in Fortran. _Derived types_ is a special form of a data type that can encapsulate other built-in types as well as other _derived types_. It could be considered as the equivalent of _struct_ in the C/C++ programming languages.
88

9-
## Declaring derived types
9+
## A quick take on derived types
1010

1111
Example of a basic derived type is:
1212

@@ -17,36 +17,99 @@ type :: my_type
1717
end type
1818
```
1919

20-
The syntax for creating a variable of type _my_type_:
21-
20+
The syntax for creating a variable of type _my_type_ and accessing its members:
2221
```fortran
22+
! declare
2323
type(my_type) :: foo
24+
! initialize
25+
foo%i = 1
26+
foo%x = 0.5
27+
```
28+
29+
{% include note.html content="In Fortran the percentage symbol `%` is used to access the members of a derived type." %}
30+
31+
To initialize the members of _my_type_ one can use either individual initialization as demonstrated in the above example, or the assignment operator (=), or the default initialization.
32+
33+
34+
Example using the assignement operator (=):
35+
```fortran
36+
foo = my_type(1, 0.5)
37+
! or using F2003 stardard and on
38+
foo = my_type(i=1, x=0.5)
2439
```
2540

26-
The members of _foo_ can be accessed as follows:
41+
Example with default initialization:
2742
```fortran
28-
foo%i
43+
type :: my_type
44+
integer :: i = 1
45+
real :: x = 0.5
46+
end type
47+
! then it is possible to use as
48+
type(my_type) :: foo
49+
foo = my_type(i=2) ! foo%i gets a new value, but foo%x retains the default one.
2950
```
30-
{% include note.html content="The use of `%` is the equivalent of `.` as used in many other languages like C/C++ and python." %}
3151

32-
## Full syntax
52+
## Derived types in detail
53+
54+
The full syntax of a derived type with all optional properties is presented below:
3355

3456
```fortran
3557
type [,attribute-list] :: name [(parameterized-decleration-list)]
3658
[parameterized-definition-statements]
3759
[private statement or sequence statement]
38-
[member-variables-decleration]
60+
[member-variables]
3961
contains
40-
[procedure decleration]
62+
[type-bound-procedures]
4163
end type
4264
```
65+
66+
### Part 1: Options to declare a derived type
67+
4368
`attribute-list` may refer to the following:
4469

4570
- _access-type_ that is either `public` or `private`
46-
- `bind(c)` interoperability with C programming language
71+
- `bind(c)` offers interoperability with C programming language
4772
- `extends(`_parent_`)` where _parent_ is the name of a previously declared derived type, from which, the current derived type will inherit all its members and functionality.
4873
- `abstract` an object orianted feature that is covered in the advanced programming tutorial.
4974

75+
{% include note.html content="If the `attribute: bind(c)` or the `statement: sequence` is used then a derived type cannot have the `attribute: extends` and visa-versa." %}
76+
77+
The `sequence` attribute may be used only to declare that the following members should be accessed in the same order as they are defined within the derived type.
78+
79+
Example with `sequence`:
80+
```fortran
81+
type :: foo
82+
sequence
83+
integer :: var1
84+
real :: var2
85+
end type
86+
! init
87+
type(foo) :: bar
88+
bar = foo(1, 0.5)
89+
```
90+
{% include note.html content="The use of statement `sequence` presupposes that the data types defined below are neither of `allocatable` nor of `pointer` type. Furthermore, it does not imply that these data types will be stored in memory in any particular form, there is no relation to `contigeous` attribute." %}
91+
92+
The _access-type_ attributes `public` and `private` if used, declare that all [member-variables] declared below will be automatically assigned the attribute accordingly.
93+
94+
The attribute `bind(c)` is used to achieve compatibility between Fortran's derived type and C's struct.
95+
96+
Example with 'bind(c)`:
97+
```fortran
98+
module mymod
99+
use iso_c_bindings
100+
implicit none
101+
type, bind(c) :: mytype
102+
integer(c_int) :: i
103+
end type
104+
```
105+
matches the following C struct:
106+
```c
107+
struct{
108+
int i
109+
}mytype;
110+
```
111+
{% include note.html content="A fortran derived type with the attribute `bind(c)` cannot have the `sequence` and `extends` attributes. Furthermore it cannot contain any Fortran `pointer` or `allocatable` types." %}
112+
50113
`parameterized-decleration-list`: is an optional feautre. If used, then the parameters must be listed in place of [parameterized-definition-statements] and must be either `len` or `kind` parameters or both.
51114

52115
Example of a derived type with `parameterized-decleration-list` and with the `attribute: public`:
@@ -72,12 +135,14 @@ end program
72135

73136
{% include important.html content="By default derived types and their members are public. However, in this example the attribute `private` is used at the beginning of the module, therefore, everything within the module will be by default `private` unless, explicitly, declared as `public`. If the type **matrix** was not given the attribute `public` in the above example, then the compiler would throw an error inside **program test**." %}
74137

75-
Example with the `attribute: extends`:
138+
The attribute `extends` was added in F2003 standard and introduces an important feature of the object oriented paradigm (OOP), namely the inheritance. It allows code reusability by letting children-derived-types like this: `type, extends(parent) :: child` to inherit all the members and functionality from a parent-derived-type: `type :: parent`.
139+
140+
Example with the attribute `extends`:
76141
```fortran
77142
module mymod
78143
implicit none
79144
private
80-
public t_date, t_address, t_person, t_employ
145+
public t_date, t_address, t_person, t_employ ! note another way of using the public attribute by gathering all public data types in one place
81146
82147
type :: t_date
83148
integer :: year, month, day
@@ -104,16 +169,130 @@ use mymod
104169
implicit none
105170
type(t_employ) :: employ
106171
107-
!example initialization
108-
employ%hired_date%year = 2020 ! t_employ has access to type(t_date) members not because of extends but because a type(t_date) was declared within employ
172+
! initialization
173+
employ%hired_date%year = 2020 ! t_employ has access to type(t_date) members not because of extends but because a type(t_date) was declared within t_employ
109174
employ%hired_date%month = 1
110175
employ%hired_date%day = 20
111176
employ%first_name = 'Johny' !t_employ has acces to t_person, and inherits its members due to extends
112177
employ%last_name = 'Doe'
113-
employ%city = 'London' ! t_employ has access to t_address, because it inherits from t_person, that in turn inherits from t_address
178+
employ%city = 'London' ! t_employ has access to t_address, because it inherits from t_person, that in return inherits from t_address
114179
employ%road_name = 'BigBen'
115180
employ%house_number = 1
116181
employ%position = 'Intern'
117182
employ%monthly_salary = 0.0
118183
end program
119-
```
184+
```
185+
186+
### Part 2: Options to declare members of a derived type
187+
188+
`[member-variables]` refers to the decleration of all the member data types. These data types can be of any built-in data type, and/or of other derived types, as already show-cased in the above examples. However, member-variables can have their own extensive syntax, in form of:
189+
`type [,member-attributes] :: name[attr-dependent-spec][init]`
190+
191+
`type`: any built-in type or other derived type
192+
193+
`member-attributes` (optional):
194+
195+
- `pointer` to specify a pointer
196+
- `allocatable` with or without `dimension` to specify a dynamic array
197+
- `public` or `private` access attributes
198+
- `protected` access attribute
199+
- `codimension` to specify a coarray
200+
- `contigeous`
201+
202+
{% include note.html content="`pointer` and `allocatable` cannot co-exist." %}
203+
204+
{% include note.html content="`contigeous` requires an array with the `pointer` attribute." %}
205+
206+
Examples for common cases:
207+
208+
```fortran
209+
type :: t_example
210+
!1st case: simple built-in type with access attribute and [init]
211+
integer, private :: i = 0 ! private hides it from use outside of the t_example's scope. The default initialization [=0] is the [init] part.
212+
213+
!2nd case: dynamic 1d_array
214+
real, allocatable, dimension(:) :: x
215+
! the same as
216+
real, allocatable :: x(:) ! parenthesis implies dimension(:) and is one of the possible [attr-dependent-spec].
217+
218+
!3rd case: protected
219+
integer, protected :: i ! In contrary to private, protected allows access to i assigned value outside of t_example but is not definable, i.e. a value may be assigned to i only within t_example.
220+
221+
!4th case: pointer, with [init]
222+
real, pointer :: x(:) => null() ! the [init] part is the [=>null()], pointers are discussed in the Advanced programming mini-book.
223+
224+
!5th case: coarray
225+
real, allocatable, codimension[:] :: z(:) ! a 1d_dynamic array shared in all threads. Coarrays will be discussed in the Advanced programming mini-book.
226+
!or
227+
real, allocatable :: z(:)[:] ! here the [:] is the [attr-dependent-spec] and implies the codimension[:].
228+
229+
!6th case: contigeous
230+
real, contigeous, pointer :: x(:)
231+
end type
232+
```
233+
234+
{% include note.html content="In the above example the cases 4, 5 and 6 make use of Fortran `pointer` and `coarray` features that have not been addressed in this quickstart tutorial. However, they are presented here, in order for the readers to know that these feautures do exist and be able to recognise them. These features will be covered in detail in the upcoming `Advanced programing` mini-book." %}
235+
236+
### Part 3: Type-bound procedures
237+
238+
A derivd type is possible to contain procedures either `functions` or `subroutines` that are **bound** to this derived type. Type procedures must follow the `contains` statement that, in return, must be used within the derived type and after all [member-variables] have been declared.
239+
240+
{% include note.html content="It is impossible to describe type-bound procedures in their full syntax without delving into OOP features of modern Fortran. For that reason only a simple example is provided in this final part, to demostrante a very besic use." %}
241+
242+
Example of a derived type with basic bound-procedure:
243+
244+
```fortran
245+
module mymod
246+
implicit none
247+
private
248+
public t_square
249+
250+
type :: t_square
251+
real :: side
252+
contains
253+
procedure :: area !procedure decleration
254+
end type
255+
256+
contains
257+
! procedure definition
258+
real function area(self) result(res)
259+
class(t_square), intent(in) :: self
260+
res = self%side * self%side
261+
end function
262+
end module
263+
264+
program main
265+
use mymod
266+
implicit none
267+
! variables decleration
268+
type(t_square) :: sq
269+
real :: x, side
270+
271+
! variables initialization
272+
side = 0.5
273+
sq%side = side
274+
275+
x = sq%area() ! self does not appear here, it has been passed implicitly
276+
! do stuff with x...
277+
end program
278+
```
279+
What is new:
280+
281+
- **self** is a random name that was chosen to represent the derived type t_square that is passed as an argument to the bound-function in order to have access to its data-members. By passing it like that it is ensured that later during its use the t_square will be passed automatically and not by the client.
282+
- in order to have the above functionality the new keyword `class` replaced the `type` one. With `class` the OOP feature *polymorphism* is introduced.
283+
- since the bound-procedure **area** was defined as a function it cannot be called by itself, it can only appear as **rhs** object, that is why it is used like `x = sq%area()`. The 'stand-alone' functionality is covered by a subroutine, and the above example should be modified like:
284+
285+
```fortran
286+
! change within module
287+
contains
288+
subroutine area(self, x)
289+
class(t_square), intent(in) :: self
290+
real, intent(in out) :: x
291+
x = self%side * self%side
292+
end subroutine
293+
294+
! change within main program
295+
call sq%area(x)
296+
! do stuff with x...
297+
```
298+
In this case there are two arguments in definition, one similar as before the **self** of type `t_square` and the second one a real variable **x** that should be assigned the calculated area and returned back for further use.

0 commit comments

Comments
 (0)