From 390c7a076e0a294f2b4c8b5662e801bdd86c3a87 Mon Sep 17 00:00:00 2001 From: smeskos Date: Thu, 4 Jun 2020 22:38:10 +0300 Subject: [PATCH 1/8] new page in quickstart: derived_types 1. added gitignore for directory: _site 2. added new link in _data\learing.yml 3. start writing the derived_types.md within learn\quickstart\ --- .gitignore | 1 + _data/learning.yml | 1 + learn/quickstart/derived_types.md | 73 +++++++++++++++++++++++++++++++ 3 files changed, 75 insertions(+) create mode 100644 .gitignore create mode 100644 learn/quickstart/derived_types.md diff --git a/.gitignore b/.gitignore new file mode 100644 index 000000000..c08f9add7 --- /dev/null +++ b/.gitignore @@ -0,0 +1 @@ +_site \ No newline at end of file diff --git a/_data/learning.yml b/_data/learning.yml index 43c2a2f50..b9e5dc064 100644 --- a/_data/learning.yml +++ b/_data/learning.yml @@ -26,6 +26,7 @@ books: - link: /learn/quickstart/arrays_strings - link: /learn/quickstart/operators_control_flow - link: /learn/quickstart/organising_code + - link: /learn/quickstart/derived_types diff --git a/learn/quickstart/derived_types.md b/learn/quickstart/derived_types.md new file mode 100644 index 000000000..4d159ad48 --- /dev/null +++ b/learn/quickstart/derived_types.md @@ -0,0 +1,73 @@ +--- +layout: book +title: Derived types +permalink: /learn/quickstart/derived_types +--- + +As discussed in sectionn [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 C/C++. + +## Declaring derived types + +Example of a basic derived type is: + +```fortran +type :: my_type + integer :: i + real :: x +end type +``` + +The syntax for creating a variable of type _my_type_ is: + +```fortran +type(my_type) :: foo +``` + +The members of _foo_ can be accessed as follows: +```fortran +foo%i +``` +Note that the use of `%` is the equivalent of `.` as used in many other languages like C/C++, python etc... + +## Full syntax + +```fortran +type [,attribute-list] :: name [(parameterized-decleration-list)] + [parameterized-definition-statements] + [private statement or sequence statement] + [member-variables-decleration] + contains + [procedure decleration] +end type +``` +`attribute-list` may refer to the following: + +- _access-type_ that is either `public` or `private` +- `bind(c)` interoperability with C programming language +- `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. +- `abstract` an object orianted feature that is covered in the advanced programming tutorial. + +`parameterized-decleration-list`: is an optional feautre, but if a derived type is parameterized then the parameters must be listed inside, in the[parameterized-definition-statements] place and must be either `len` or `kind` parameters or both. + +Example of a derived type with `parameterized-decleration-list` and with `attribute`: `public`: + ```fortran +module mymod +implicit none +private + +type, public :: matrix(rows, cols, k) + integer, len :: rows, cols + integer, kind :: k = kind(0.0) + real(kind = k), dimension(rows, cols) :: values +end type matrix +end module + +program test +use mymod +implicit none +type(matrix(rows=5, cols=5)) :: m +end program + ``` +{% include note.html content="In this example the parameter **k** has already been assigned a default value of `kind(0.0)`, that is of floating point single precision, for that reason it can be ommited, as it is the case here in the declaration inside the main program."} + +{% include important.html content="By default __derived types__ and their members are public. Hhowever, in this example the attribute __private__ is used at the beginning of the module, therefore, everything within the modure 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__."} \ No newline at end of file From 3199de1108fca99a571a8c86e253ac86769c9251 Mon Sep 17 00:00:00 2001 From: smeskos Date: Thu, 4 Jun 2020 22:41:30 +0300 Subject: [PATCH 2/8] typo corrected in derived_types.md --- learn/quickstart/derived_types.md | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/learn/quickstart/derived_types.md b/learn/quickstart/derived_types.md index 4d159ad48..ee384b54c 100644 --- a/learn/quickstart/derived_types.md +++ b/learn/quickstart/derived_types.md @@ -68,6 +68,6 @@ implicit none type(matrix(rows=5, cols=5)) :: m end program ``` -{% include note.html content="In this example the parameter **k** has already been assigned a default value of `kind(0.0)`, that is of floating point single precision, for that reason it can be ommited, as it is the case here in the declaration inside the main program."} +{% include note.html content="In this example the parameter **k** has already been assigned a default value of `kind(0.0)`, that is of floating point single precision, for that reason it can be ommited, as it is the case here in the declaration inside the main program." %} -{% include important.html content="By default __derived types__ and their members are public. Hhowever, in this example the attribute __private__ is used at the beginning of the module, therefore, everything within the modure 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__."} \ No newline at end of file +{% include important.html content="By default __derived types__ and their members are public. Hhowever, in this example the attribute __private__ is used at the beginning of the module, therefore, everything within the modure 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__." %} \ No newline at end of file From ff558915dd2d278d71d9786464af5f052d7df235 Mon Sep 17 00:00:00 2001 From: smeskos Date: Fri, 5 Jun 2020 01:48:53 +0300 Subject: [PATCH 3/8] typos and new example with extends --- learn/quickstart/derived_types.md | 58 +++++++++++++++++++++++++++---- 1 file changed, 52 insertions(+), 6 deletions(-) diff --git a/learn/quickstart/derived_types.md b/learn/quickstart/derived_types.md index ee384b54c..fb6cb83e0 100644 --- a/learn/quickstart/derived_types.md +++ b/learn/quickstart/derived_types.md @@ -4,7 +4,7 @@ title: Derived types permalink: /learn/quickstart/derived_types --- -As discussed in sectionn [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 C/C++. +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. ## Declaring derived types @@ -17,7 +17,7 @@ type :: my_type end type ``` -The syntax for creating a variable of type _my_type_ is: +The syntax for creating a variable of type _my_type_: ```fortran type(my_type) :: foo @@ -27,7 +27,7 @@ The members of _foo_ can be accessed as follows: ```fortran foo%i ``` -Note that the use of `%` is the equivalent of `.` as used in many other languages like C/C++, python etc... +{% include note.html content="The use of `%` is the equivalent of `.` as used in many other languages like C/C++ and python." %} ## Full syntax @@ -47,9 +47,9 @@ end type - `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. - `abstract` an object orianted feature that is covered in the advanced programming tutorial. -`parameterized-decleration-list`: is an optional feautre, but if a derived type is parameterized then the parameters must be listed inside, in the[parameterized-definition-statements] place and must be either `len` or `kind` parameters or both. +`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. -Example of a derived type with `parameterized-decleration-list` and with `attribute`: `public`: +Example of a derived type with `parameterized-decleration-list` and with the `attribute: public`: ```fortran module mymod implicit none @@ -70,4 +70,50 @@ end program ``` {% include note.html content="In this example the parameter **k** has already been assigned a default value of `kind(0.0)`, that is of floating point single precision, for that reason it can be ommited, as it is the case here in the declaration inside the main program." %} -{% include important.html content="By default __derived types__ and their members are public. Hhowever, in this example the attribute __private__ is used at the beginning of the module, therefore, everything within the modure 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__." %} \ No newline at end of file +{% 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**." %} + +Example with the `attribute: extends`: +```fortran +module mymod +implicit none +private +public t_date, t_address, t_person, t_employ + +type :: t_date + integer :: year, month, day +end type + +type :: t_address + character(len=:), allocatable :: city, road_name + integer :: house_number +end type + +type, extends(t_address) :: t_person + character(len=:), allocatable :: first_name, last_name, e_mail +end type + +type, extends(t_person) :: t_employ + type(t_date) :: hired_date + character(len=:), allocatable :: position + real :: monthly_salary +end type +end module + +program test +use mymod +implicit none +type(t_employ) :: employ + +!example initialization +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 +employ%hired_date%month = 1 +employ%hired_date%day = 20 +employ%first_name = 'Johny' !t_employ has acces to t_person, and inherits its members due to extends +employ%last_name = 'Doe' +employ%city = 'London' ! t_employ has access to t_address, because it inherits from t_person, that in turn inherits from t_address +employ%road_name = 'BigBen' +employ%house_number = 1 +employ%position = 'Intern' +employ%monthly_salary = 0.0 +end program +``` \ No newline at end of file From 814f6579fab2acf0d8bd1e27150330e1fbe14757 Mon Sep 17 00:00:00 2001 From: smeskos Date: Fri, 5 Jun 2020 19:07:33 +0300 Subject: [PATCH 4/8] Completed tutorial 1. added all three parts 2. corrected typos --- learn/quickstart/derived_types.md | 213 +++++++++++++++++++++++++++--- 1 file changed, 196 insertions(+), 17 deletions(-) diff --git a/learn/quickstart/derived_types.md b/learn/quickstart/derived_types.md index fb6cb83e0..5cc68dc14 100644 --- a/learn/quickstart/derived_types.md +++ b/learn/quickstart/derived_types.md @@ -4,9 +4,9 @@ title: Derived types permalink: /learn/quickstart/derived_types --- -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. +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. -## Declaring derived types +## A quick take on derived types Example of a basic derived type is: @@ -17,36 +17,99 @@ type :: my_type end type ``` -The syntax for creating a variable of type _my_type_: - +The syntax for creating a variable of type _my_type_ and accessing its members: ```fortran +! declare type(my_type) :: foo +! initialize +foo%i = 1 +foo%x = 0.5 +``` + +{% include note.html content="In Fortran the percentage symbol `%` is used to access the members of a derived type." %} + +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. + + +Example using the assignement operator (=): +```fortran +foo = my_type(1, 0.5) +! or using F2003 stardard and on +foo = my_type(i=1, x=0.5) ``` -The members of _foo_ can be accessed as follows: +Example with default initialization: ```fortran -foo%i +type :: my_type + integer :: i = 1 + real :: x = 0.5 +end type +! then it is possible to use as +type(my_type) :: foo +foo = my_type(i=2) ! foo%i gets a new value, but foo%x retains the default one. ``` -{% include note.html content="The use of `%` is the equivalent of `.` as used in many other languages like C/C++ and python." %} -## Full syntax +## Derived types in detail + +The full syntax of a derived type with all optional properties is presented below: ```fortran type [,attribute-list] :: name [(parameterized-decleration-list)] [parameterized-definition-statements] [private statement or sequence statement] - [member-variables-decleration] + [member-variables] contains - [procedure decleration] + [type-bound-procedures] end type ``` + +### Part 1: Options to declare a derived type + `attribute-list` may refer to the following: - _access-type_ that is either `public` or `private` -- `bind(c)` interoperability with C programming language +- `bind(c)` offers interoperability with C programming language - `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. - `abstract` an object orianted feature that is covered in the advanced programming tutorial. +{% 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." %} + +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. + +Example with `sequence`: +```fortran +type :: foo +sequence +integer :: var1 +real :: var2 +end type +! init +type(foo) :: bar +bar = foo(1, 0.5) +``` +{% 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." %} + +The _access-type_ attributes `public` and `private` if used, declare that all [member-variables] declared below will be automatically assigned the attribute accordingly. + +The attribute `bind(c)` is used to achieve compatibility between Fortran's derived type and C's struct. + +Example with 'bind(c)`: +```fortran +module mymod +use iso_c_bindings +implicit none +type, bind(c) :: mytype + integer(c_int) :: i +end type +``` +matches the following C struct: +```c +struct{ + int i +}mytype; +``` +{% 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." %} + `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. Example of a derived type with `parameterized-decleration-list` and with the `attribute: public`: @@ -72,12 +135,14 @@ end program {% 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**." %} -Example with the `attribute: extends`: +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`. + +Example with the attribute `extends`: ```fortran module mymod implicit none private -public t_date, t_address, t_person, t_employ +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 type :: t_date integer :: year, month, day @@ -104,16 +169,130 @@ use mymod implicit none type(t_employ) :: employ -!example initialization -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 +! initialization +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 employ%hired_date%month = 1 employ%hired_date%day = 20 employ%first_name = 'Johny' !t_employ has acces to t_person, and inherits its members due to extends employ%last_name = 'Doe' -employ%city = 'London' ! t_employ has access to t_address, because it inherits from t_person, that in turn inherits from t_address +employ%city = 'London' ! t_employ has access to t_address, because it inherits from t_person, that in return inherits from t_address employ%road_name = 'BigBen' employ%house_number = 1 employ%position = 'Intern' employ%monthly_salary = 0.0 end program -``` \ No newline at end of file +``` + +### Part 2: Options to declare members of a derived type + +`[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: +`type [,member-attributes] :: name[attr-dependent-spec][init]` + +`type`: any built-in type or other derived type + +`member-attributes` (optional): + +- `pointer` to specify a pointer +- `allocatable` with or without `dimension` to specify a dynamic array +- `public` or `private` access attributes +- `protected` access attribute +- `codimension` to specify a coarray +- `contigeous` + +{% include note.html content="`pointer` and `allocatable` cannot co-exist." %} + +{% include note.html content="`contigeous` requires an array with the `pointer` attribute." %} + +Examples for common cases: + +```fortran +type :: t_example + !1st case: simple built-in type with access attribute and [init] + integer, private :: i = 0 ! private hides it from use outside of the t_example's scope. The default initialization [=0] is the [init] part. + + !2nd case: dynamic 1d_array + real, allocatable, dimension(:) :: x + ! the same as + real, allocatable :: x(:) ! parenthesis implies dimension(:) and is one of the possible [attr-dependent-spec]. + + !3rd case: protected + 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. + + !4th case: pointer, with [init] + real, pointer :: x(:) => null() ! the [init] part is the [=>null()], pointers are discussed in the Advanced programming mini-book. + + !5th case: coarray + real, allocatable, codimension[:] :: z(:) ! a 1d_dynamic array shared in all threads. Coarrays will be discussed in the Advanced programming mini-book. + !or + real, allocatable :: z(:)[:] ! here the [:] is the [attr-dependent-spec] and implies the codimension[:]. + + !6th case: contigeous + real, contigeous, pointer :: x(:) +end type +``` + +{% 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." %} + +### Part 3: Type-bound procedures + +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. + +{% 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." %} + +Example of a derived type with basic bound-procedure: + +```fortran +module mymod +implicit none +private +public t_square + +type :: t_square + real :: side + contains + procedure :: area !procedure decleration +end type + +contains + ! procedure definition + real function area(self) result(res) + class(t_square), intent(in) :: self + res = self%side * self%side + end function +end module + +program main +use mymod +implicit none +! variables decleration +type(t_square) :: sq +real :: x, side + +! variables initialization +side = 0.5 +sq%side = side + +x = sq%area() ! self does not appear here, it has been passed implicitly +! do stuff with x... +end program +``` +What is new: + + - **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. + - in order to have the above functionality the new keyword `class` replaced the `type` one. With `class` the OOP feature *polymorphism* is introduced. + - 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: + + ```fortran + ! change within module + contains + subroutine area(self, x) + class(t_square), intent(in) :: self + real, intent(in out) :: x + x = self%side * self%side + end subroutine + +! change within main program +call sq%area(x) +! do stuff with x... + ``` + 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. \ No newline at end of file From eed20b4cf04b24bdc15995a8a5b42932abf8e5ad Mon Sep 17 00:00:00 2001 From: smeskos Date: Fri, 5 Jun 2020 19:20:32 +0300 Subject: [PATCH 5/8] typo --- learn/quickstart/derived_types.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/learn/quickstart/derived_types.md b/learn/quickstart/derived_types.md index 5cc68dc14..6c769858a 100644 --- a/learn/quickstart/derived_types.md +++ b/learn/quickstart/derived_types.md @@ -8,7 +8,7 @@ As discussed previously in [Variables]({{site.baseurl}}/learn/quickstart/variabl ## A quick take on derived types -Example of a basic derived type is: +Example of a basic derived type: ```fortran type :: my_type From 82487cee6fdcf03d305c262ba46a9442541de6c9 Mon Sep 17 00:00:00 2001 From: smeskos Date: Fri, 5 Jun 2020 19:42:05 +0300 Subject: [PATCH 6/8] removed .gitignore --- .gitignore | 1 - _site/CONTRIBUTING.md | 136 +++ _site/MINIBOOKS.md | 317 ++++++ _site/PACKAGES.md | 151 +++ _site/assets/css/main.css | 440 ++++++++ _site/assets/css/syntax.css | 73 ++ _site/assets/img/discourse.png | Bin 0 -> 9544 bytes _site/assets/img/fortran-logo.svg | 98 ++ _site/assets/img/fortran_logo_128x128.png | Bin 0 -> 2977 bytes _site/assets/img/fortran_logo_256x256.png | Bin 0 -> 5990 bytes _site/assets/img/fortran_logo_512x512.png | Bin 0 -> 12591 bytes _site/assets/img/fortran_logo_64x64.png | Bin 0 -> 1563 bytes _site/assets/img/fortran_logo_grey.png | Bin 0 -> 19657 bytes _site/assets/img/fortran_logo_purple_orig.png | Bin 0 -> 234956 bytes _site/assets/img/icons/icon-menu.svg | 13 + _site/assets/js/page_nav.js | 35 + _site/compilers/index.html | 411 ++++++++ _site/favicon.ico | Bin 0 -> 16958 bytes _site/index.html | 353 +++++++ _site/learn/best_practices.html | 244 +++++ _site/learn/index.html | 331 ++++++ _site/learn/quickstart.html | 469 +++++++++ _site/learn/quickstart/arrays_strings.html | 631 ++++++++++++ _site/learn/quickstart/derived_types.html | 804 +++++++++++++++ _site/learn/quickstart/hello_world.html | 543 ++++++++++ .../quickstart/operators_control_flow.html | 670 ++++++++++++ _site/learn/quickstart/organising_code.html | 671 ++++++++++++ _site/learn/quickstart/variables.html | 708 +++++++++++++ _site/news.xml | 465 +++++++++ _site/news/archive/index.html | 188 ++++ _site/news/index.html | 741 ++++++++++++++ .../2020/02/28/J3-february-meeting/index.html | 251 +++++ .../06/Announcing-FortranCon-2020/index.html | 182 ++++ .../2020/04/18/Fortran-Webinar/index.html | 178 ++++ .../01/Fortran-Newsletter-May-2020/index.html | 295 ++++++ .../Fortran-Newsletter-June-2020/index.html | 300 ++++++ _site/packages/data-types.html | 436 ++++++++ _site/packages/examples.html | 283 ++++++ _site/packages/graphics.html | 385 +++++++ _site/packages/index.html | 566 +++++++++++ _site/packages/interfaces.html | 620 ++++++++++++ _site/packages/io.html | 589 +++++++++++ _site/packages/libraries.html | 406 ++++++++ _site/packages/numerical.html | 721 +++++++++++++ _site/packages/preview.html | 204 ++++ _site/packages/programming.html | 370 +++++++ _site/packages/projects_json.js | 953 ++++++++++++++++++ _site/packages/projects_search.js | 154 +++ _site/packages/scientific.html | 602 +++++++++++ _site/packages/search/index.html | 174 ++++ _site/packages/strings.html | 312 ++++++ 51 files changed, 16473 insertions(+), 1 deletion(-) delete mode 100644 .gitignore create mode 100644 _site/CONTRIBUTING.md create mode 100644 _site/MINIBOOKS.md create mode 100644 _site/PACKAGES.md create mode 100644 _site/assets/css/main.css create mode 100644 _site/assets/css/syntax.css create mode 100644 _site/assets/img/discourse.png create mode 100644 _site/assets/img/fortran-logo.svg create mode 100644 _site/assets/img/fortran_logo_128x128.png create mode 100644 _site/assets/img/fortran_logo_256x256.png create mode 100644 _site/assets/img/fortran_logo_512x512.png create mode 100644 _site/assets/img/fortran_logo_64x64.png create mode 100644 _site/assets/img/fortran_logo_grey.png create mode 100644 _site/assets/img/fortran_logo_purple_orig.png create mode 100644 _site/assets/img/icons/icon-menu.svg create mode 100644 _site/assets/js/page_nav.js create mode 100644 _site/compilers/index.html create mode 100644 _site/favicon.ico create mode 100644 _site/index.html create mode 100644 _site/learn/best_practices.html create mode 100644 _site/learn/index.html create mode 100644 _site/learn/quickstart.html create mode 100644 _site/learn/quickstart/arrays_strings.html create mode 100644 _site/learn/quickstart/derived_types.html create mode 100644 _site/learn/quickstart/hello_world.html create mode 100644 _site/learn/quickstart/operators_control_flow.html create mode 100644 _site/learn/quickstart/organising_code.html create mode 100644 _site/learn/quickstart/variables.html create mode 100644 _site/news.xml create mode 100644 _site/news/archive/index.html create mode 100644 _site/news/index.html create mode 100644 _site/newsletter/2020/02/28/J3-february-meeting/index.html create mode 100644 _site/newsletter/2020/04/06/Announcing-FortranCon-2020/index.html create mode 100644 _site/newsletter/2020/04/18/Fortran-Webinar/index.html create mode 100644 _site/newsletter/2020/05/01/Fortran-Newsletter-May-2020/index.html create mode 100644 _site/newsletter/2020/06/01/Fortran-Newsletter-June-2020/index.html create mode 100644 _site/packages/data-types.html create mode 100644 _site/packages/examples.html create mode 100644 _site/packages/graphics.html create mode 100644 _site/packages/index.html create mode 100644 _site/packages/interfaces.html create mode 100644 _site/packages/io.html create mode 100644 _site/packages/libraries.html create mode 100644 _site/packages/numerical.html create mode 100644 _site/packages/preview.html create mode 100644 _site/packages/programming.html create mode 100644 _site/packages/projects_json.js create mode 100644 _site/packages/projects_search.js create mode 100644 _site/packages/scientific.html create mode 100644 _site/packages/search/index.html create mode 100644 _site/packages/strings.html diff --git a/.gitignore b/.gitignore deleted file mode 100644 index c08f9add7..000000000 --- a/.gitignore +++ /dev/null @@ -1 +0,0 @@ -_site \ No newline at end of file diff --git a/_site/CONTRIBUTING.md b/_site/CONTRIBUTING.md new file mode 100644 index 000000000..022284e51 --- /dev/null +++ b/_site/CONTRIBUTING.md @@ -0,0 +1,136 @@ +# Contributing to fortran-lang.github.io + +Fortran-lang.github.io is open-source and contributions are welcome! +The Fortran-lang site uses the Ruby-based [Jekyll static site generator](https://jekyllrb.com/). +To contribute you will therefore need to install Jekyll on your development computer. +See [README.md](README.md) for how to setup Jekyll and build the site. + +* See [PACKAGES](./PACKAGES.md) for how to add an entry to the [Package index](https://fortran-lang.org/packages) + +* See [MINIBOOKS](./MINIBOOKS.md) for how to write and structure a mini-book tutorial for the [Learn](https://fortran-lang.org/learn) section + +## Workflow + +Contributions to the site are made by pull request to the github repository: . + +The workflow for doing so takes the following form: + +1. Create/update a personal fork of fortran-lang.github.io + - (See [github help: syncing a fork](https://help.github.com/en/github/collaborating-with-issues-and-pull-requests/syncing-a-fork) ) + +2. Create a new branch in your fork + - The branch name should concisely describe your contribution, _e.g._ `fix-spelling-homepage`, `update-compiler-info` + +3. Perform your changes on the local branch + +4. Push your modified branch to your local fork + - _e.g._ `git push --set-upstream origin fix-spelling-homepage` + +5. Create a pull request in the fortran-lang/fortran-lang.github.io from your modified fork branch + - (See [github help: creating a pull request](https://help.github.com/en/github/collaborating-with-issues-and-pull-requests/creating-a-pull-request) ) + +__Note: Before opening a pull request you must build your changes locally using Jekyll (see [README.md](README.md)) to verify that your changes build correctly and render as you expect.__ + +Your pull request will be reviewed by other members of the community who may request changes. + +__Note: You can continue to push changes to your fork branch after you open a pull request - the pull request will update accordingly__ + +Once your pull request is approved, usually by at least two other community members, it will be merged into the fortran-lang.github.io master branch by the maintainers at which point it will be published to the fortran-lang.org site. + +If required, the repository maintainers can build a public preview of your proposed changes which will be available to view at `fortran-lang.org/pr//` where `` is the numeric identifier of your pull request. + +This allows reviewers to directly view the generated result of your PR. +After a pull request has been merged and successfully rendered, the maintainers will delete the preview build. + + +## Style guide + +### External links + +It is recommended practice for off-site hyperlinks to open in a new tab. +On `Fortran-lang.org` all such links will automatically be suffixed with a new-tab icon; +this gives site users prior expectation that the link will lead them off-site while +keeping fortran-lang.org open in a previous tab. + +__Example:__ Open link in new tab (HTML or markdown) +```html +Discourse +``` + +### Internal site links + +Hyperlinks that point to other parts of the fortran-lang.org website should be prefixed with `{{ site.baseurl }}` - this is important for generating pull request previews (see [here](https://byparker.com/blog/2014/clearing-up-confusion-around-baseurl/) for an explanation). + +__Example:__ markdown link + +``` +[Fortran-lang news]({{site.baseurl}}/News) +``` + +__Example:__ html link + +``` +Fortran packages +``` + +### Icon packs + +Icons are an easy way to improve page aesthetic by breaking-up otherwise monotonic text passages +and drawing attention to headings or key information. + +Three icon packs are available for use on `fortran-lang.org`: + +* [Font awesome](https://fontawesome.com/icons?d=gallery) (CC BY 4.0 License) + +* [Feather](https://feathericons.com/) (MIT) + +* [Devicon](https://konpa.github.io/devicon/) (MIT) + + +__Example:__ Font awesome +```html + +``` + +__Example:__ Feather + +```html + +``` + +__Example:__ Devicon + +```html + +``` + +Visit the respective websites to browse available icons. + +__Note:__ font-awesome icons currently appear to vertically-align with text better - +we need to get feather icons to do the same. + + +### Page contents + +It is sometimes useful to display a hyperlinked page contents for lengthy pages. +There are two ways to do this on `fortran-lang.org`. + +__Option 1: Use the `book` layout__ + +The `book` layout is the layout used for mini-book tutorials; +it includes a non-scrolling sidebar which is automatically populated +by the `

` headings on the current page. + +__Option 2:__ + +If you just want a list of headings at the top of your page, +include the following snippet, which will be automatically +populated by the `

` headings on the current page. + +```html + +``` + +__Implementation:__ +the functionality described above is implemented in the javascript file +[assets/js/page_nav.js](./assets/js/page_nav.js). diff --git a/_site/MINIBOOKS.md b/_site/MINIBOOKS.md new file mode 100644 index 000000000..c4fd9b88a --- /dev/null +++ b/_site/MINIBOOKS.md @@ -0,0 +1,317 @@ +# Mini-book Tutorials on fortran-lang.org + +This guide will cover how to write mini-book tutorials for the [Learn](https://fortran-lang.org/learn) +section of . + +See [CONTRIBUTING](./CONTRIBUTING.md) for general guidance on contributing to . + +## 0. Mini-book formats + +Mini-books are designed to be mostly self-contained tutorials on a particular feature +of the Fortran language. + +There are two types of mini-book format: + +* __Single-page:__ all content is written within a single markdown file and displayed +on a single webpage; + +* __Multi-page:__ tutorial content is written across multiple markdown files and displayed +as a collection of webpages. + + +The choice of book type depends on the length of your content and how you intend to structure it. + +Consider the table of contents that will be produced: + +* Single-page books have __one level__ of navigation: a link for each `

` heading in the tutorial + +* Multi-page books have __two levels__ of navigation: a link for each page, and a link for each `

` heading on the current page + +Single-page mini-books are simpler to produce and should be used for brief topics or short tutorials that will +eventually be subsumed into a more-comprehensive multi-page book. + +Multi-page books are recommended for more-comprehensive tutorials that can be structured with one subtopic per page. + +The rest of this guide is split into two sections, one each for the single-page and multi-page book types. + +## 1. Single-page mini-book + +The steps required for publishing a single-page mini-book are: + +* Create a new markdown document in the `./learn` directory + +* Write your tutorial content + +* Add an entry to [_data/learning.yml](./_data/learning.yml) for your new mini-book + +* Open a pull request + +### 1.1 Writing your mini-book in markdown + +For single-page mini-books your tutorial will be entirely contained within a single markdown document. + +First create a new markdown document in the `./learn/` directory with the `.md` file extension +and a short name that concisely describes the topic of your tutorial, _e.g._ `./learn/file_io.md`. + +Open your new markdown file and add a header in the following format: + +``` +--- +layout: book +title: +permalink: /learn/ +--- +``` + +You should replace `` with a human-readable description of your tutorial content; +this will be displayed as an `

` heading at the top of your mini-book page. + +Replace `` with the filename of your markdown file +but __excluding the `.md` extension__. There should also be no trailing slash. + + +__Example:__ header + +``` +--- +layout: book +title: Reading and writing files in Fortran +permalink: /learn/file_io +--- +``` + +__NOT:__ `permalink: /learn/file_io.md` + +__NOT:__ `permalink: /learn/file_io/` + +You can now fill the rest of the file with your tutorial content written in markdown; +see [Kramdown syntax](https://kramdown.gettalong.org/syntax.html) for documentation on +the markdown implementation. + + +### 1.2 Structuring your mini-book with headings + +You should use `

` headings to break-up your single-page mini-book into a logical +structure. +Each `

` heading will show up in the hyperlinked table-of-contents. + +In markdown, `

` headings can be written as: + +```markdown + +My heading +---------- + +``` + +__OR__ + +```markdown + +## My heading + +``` + +__OR__ + + +```markdown + +## My heading ## + +``` + +__Note:__ make sure to include a blank line before your heading. + + +### 1.3 Add your mini-book to the Learn page + +To add your new mini-book to the _Learn_ page, you need to add a new entry +in the [_data/learning.yml](./_data/learning.yml) datafile. + +Open this file and create a new entry under the `books:` field in the following format: + +```yaml + + - title: + description: + category: + link: /learn/ + +``` + +The `title` field is what will be displayed on the _Learn_ page for your mini-book +and should generally be the same as the `title` field in your markdown file, but this isn't required. + +The contents of the `description` field is also displayed on the _Learn_ page +and should briefly summarise the contents of your mini-book tutorial. + +The `category` field should match one of the categories listed at the top of the data file (under +the `categories:` field) and is used to group tutorials on the Learn page. + +The `link` field should exactly match the `permalink` field in your markdown document. + +__Example:__ `learning.yml` book entry + +```yaml + + - title: File input and output + description: A tutorial on reading and writing files in Fortran + category: Getting started + link: /learn/file_io + +``` + +Save the modified `learning.yml` data file and rebuild the website on your local machine to check the results. +If successful, a new link should appear on the _Learn_ page with the title of your new mini-book. + +Once you have completed your mini-book and added an entry to the `learning.yml` data file, open a pull request +at (see [CONTRIBUTING](./CONTRIBUTING.md)). + + + +## 2. Multi-page mini-books + +The steps required for publishing a multi-page mini-book are: + +* Create a new folder in the `./learn/` directory + +* Create an `index.md` file in your new folder + +* Write your tutorial content in markdown files in your new folder + +* Add an entry to [_data/learning.yml](./_data/learning.yml) for your new mini-book + +* Open a pull request + + +### 2.1 Create a new folder for your mini-book + +Create a new folder in the `./learn/` directory with a short name that concisely describes the topic of your tutorial, _e.g._ `./learn/coarrays/`. +All pages of your mini-book will be contained within this folder. + +The first page of your mini-book should be called `index.md`, so create a new markdown file in +your mini-book folder called `index.md`, and add a header in the following format: + + +``` +--- +layout: book +title: +permalink: /learn/ +--- +``` + +The `title` field should contain a human-readable description of your mini-book tutorial +and this will be displayed as an `

` heading at the top of this first page. + +The `permalink` field should contain `/learn/` followed by the name of your mini-book folder. +__There should be no trailing slash.__ + +__Example:__ header for `index.md` +``` +--- +layout: book +title: Parallel programming with Coarrays +permalink: /learn/coarrays +--- +``` + +__NOT:__ `permalink: /learn/coarrays/` + +In your table of contents, this first page will be displayed as '_Introduction_'; +you should populate the remainder of `index.md` with an introduction to your +mini-book tutorial which may include: a summary of the concepts covered; any prerequisites; and +any references to other related mini-books or useful third-party resources. + +### 2.2 Add pages to your mini-book + +For each new page in your mini-book, create a new markdown file in your mini-book folder. +Each page needs a header, just like the `index.md`, but the `title` and `permalink` fields +must be unique to each new page. + +``` +--- +layout: book +title: +permalink: /learn// +--- + +``` +Replace `` with the title of your new page; this will be displayed as +an `

` header at the top of the page and in the hyperlinked table-of-contents. + +Replace `` with the name of the markdown file for your new page +but __excluding the `.md` extension__. + +__Example:__ a header for a new page `./learn/coarrays/background.md` + +``` +--- +layout: book +title: What are coarrays? +permalink: /learn/coarrays/background +--- +``` + +As with single-page mini-books, you should use `

` headings to break-up each +page into a logical structure. +Each `

` heading on the current page will show up in the hyperlinked table-of-contents. + + + + +### 2.3 Add your mini-book to the Learn page + +To add your new mini-book to the _Learn_ page, you need to add a new entry +in the [_data/learning.yml](./_data/learning.yml) datafile. + +Open this file and create a new entry under the `books:` field in the following format: + +```yaml + + - title: + description: + category: + link: /learn/ + pages: + - link: /learn// + - link: /learn// + - link: /learn// + +``` + +The `title` field is what will be displayed on the _Learn_ page for your mini-book +and should generally be the same as the `title` field in your `index.md` markdown file, but this isn't required. + +The contents of the `description` field is also displayed on the _Learn_ page +and should briefly summarise the contents of your mini-book tutorial. + +The `category` field should match one of the categories listed at the top of the data file (under +the `categories:` field) and is used to group tutorials on the Learn page. + +The top-level `link` field should exactly match the `permalink` field in your `index.md` file. + +Each `link` field under `pages` should exactly match the `permalink` field in each of your subsequent mini-book pages. +Pages are listed in the table-of-contents in the order that they are listed under `pages`. + +__Example:__ `learning.yml` book entry + +```yaml + + - title: Parallel programming with Coarrays + description: A tutorial on parallel programming using coarrays + category: Parallel programming + link: /learn/coarrays + pages: + - link: /learn/coarrays/background + - link: /learn/coarrays/codimension + - link: /learn/coarrays/examples + +``` + +Save the modified `learning.yml` data file and rebuild the website on your local machine to check the results. +If successful, a new link should appear on the _Learn_ page with the title of your new mini-book. + +Once you have completed your mini-book and added an entry to the `learning.yml` data file, open a pull request +at (see [CONTRIBUTING](./CONTRIBUTING.md)). diff --git a/_site/PACKAGES.md b/_site/PACKAGES.md new file mode 100644 index 000000000..1b1969bd0 --- /dev/null +++ b/_site/PACKAGES.md @@ -0,0 +1,151 @@ +# Fortran-lang.org package index + + +## Package criteria + +The following criteria are required of packages to be indexed: + +- __Relevance__: the package must be primarily implemented in Fortran or provide +a complete Fortran interface to an existing package or be purposed solely towards +software development in Fortran. + +- __Maturity__: the primary functionality of the package shall be implemented. +No prototype, testing or partially complete packages will be accepted. +If the package is hosted on github or similar, it should have at least 5 'stars'. + +- __Availability__: the package source shall be freely available for browsing online +or cloning or downloading + +- __Open source__: the package shall be licensed under an appropriate [open-source license](https://opensource.org/licenses) +with the license file clearly included with the source code + +- __Uniqueness__: the package shall not be a fork or minor revision of existing packages + +- __README__: the package shall have some form of README or landing-page clearly +stating the package purpose and functionality. This should also contain information +on the package dependencies and the steps required to build and run. + + +The following criteria are not required but are recommended: + +- __Documentation__: any form of written documentation aimed at users of the package. Ideally +this should cover: + - Supported / tested compilers + - Dependencies + - Build and install process + - Modules contained within the package + - Procedures made available and their interfaces + - Example code + +- __Contributing__: details on how users may submit issues and contribute to the development of the +package + +- __Tests__: any form of executable test(s) that can be used to verify the functionality of the package + +- __Portability__: no non-standard language extensions or proprietary dependencies + +- __FPM__: support installation by the Fortran Package Manager [fpm](https://github.com/fortran-lang/fpm) + + +## Process for adding packages + +1. Users should confirm that their project meets the minimum requirements for listing in the +Fortran-lang package index, as written in this document + +2. Users should open a pull request using the 'Package index request' template + +3. At least three Fortran-lang community members shall review the request against the criteria above + +4. If three or more Fortran-lang community members agree that the package should be listed and there is no significant objection, then the pull request will be merged + + +## Package index requests + +Package index requests are made by pull requests against the [fortran-lang.github.io repository](https://github.com/fortran-lang/fortran-lang.github.io/). +See [this guide](https://guides.github.com/activities/forking/) for guidance on forking and making pull requests. + +Package details are listed in the `_data/package_index.yml` data file. + +To add a package simply create a new entry within this file. +The data file is ordered by high-level categories merely to aid in navigation; +find the appropriate category for your package and create a new entry. + +### Github hosted packages + +``` + - name: + github: / + description: + categories: [category2] + tags: [tag1] [tag2] [tag3] + version: [version] + license: [license] +``` + +Valid categories: +- `libraries`: general libraries +- `interfaces`: libraries that provide interfaces to other libraries, software or devices +- `programming`: general programming utilities: errors, logging, testing, documentation _etc._ +- `data-types`: libraries providing advanced data types: containers, datetime, resizable arrays _etc._ +- `strings`: string handling libraries +- `io`: libraries that parse and generate various file formats +- `graphics`: plotting and GUIs +- `numerical`: matrices, linear algebra, solvers, root-finding, interpolation, optimization, differential eqns, statistics, machine learning, random numbers _etc._ +- `scientific`: domain-specific scientific libraries or applications +- `examples`: repositories offering language feature demonstrations, tutorials and benchmarks + +__Projects listing more than one category must provide good justification thereof +in the pull request.__ + +__Notes:__ + +- The package description should clearly describe the functionality of the package in a single sentence. + +- Tags (optional) should contain any terms not already contained in the name or description that users may search directly for. Tags should be separate by spaces. + +- Package version + - this can be determined automatically if a versioned release has been created on github + - if version is specified, it will override any detected github version + - if version is 'none', then no version information will be displayed. (Use this if + your package has no version.) + +- Package license + - this can be determined automatically if github is able to detect a known license + - license must be specified if github is unable to detect a known license + +### Non-github hosted packages + +``` + - name: + url: + description: + categories: [category2] + tags: [tag1] [tag2] [tag3] + version: [version] + license: +``` + +__Notes:__ + +- License and version information cannot be detected automatically for non-github repositories +- if your package has no version, then omit the version field +- a license must be specified for non-github repositories + + +### Member review checklist + +Community members reviewing packages should cover the following points: + +1. Ensure the package meets the minimum criteria as written in this document + +2. Check the package metadata + - Repository exists and is accessible + - Description clearly and concisely describes the package + - Assigned category is appropriate + +3. Check license information + - If license field has been omitted: check that github has detected the license + - If license field is included: check that it matches repository license file + +After merge: + - Check that package is available in expected category and search \ No newline at end of file diff --git a/_site/assets/css/main.css b/_site/assets/css/main.css new file mode 100644 index 000000000..5e7a317d2 --- /dev/null +++ b/_site/assets/css/main.css @@ -0,0 +1,440 @@ +* { + -moz-box-sizing: border-box; + box-sizing: border-box; +} + +body { + font-family: 'Helvetica Neue', Helvetica, Arial, sans-serif; + font-size: 15px; + line-height: 1.4; + color: #444; + background-color: #fbfbfb; +} +@media (min-width: 568px) { + body { + font-size: 17px; + } +} + +a { + color: #3c92d1; + text-decoration: none; +} + +.current a { + font-weight: bold; +} + +.button { + background-color: #734f96; + border: none; + color: white; + padding: 10px 32px; + text-align: center; + text-decoration: none; + display: inline-block; + font-size: 20px; + border-radius: 8px; +} + +.button.center { + display: block; + margin: 0 auto; + width: fit-content; +} + +.button:hover { + background-color: #777; + color: white; + text-decoration: none; +} + +.button.blue{ + background-color: #008CBA; +} + +.button.blue:hover{ + background-color: #777; +} + +#page-nav { + padding-left: 20px; +} + +h1, +h2, +h3 { + font-family: 'Lato', sans-serif; +} + +h1 { + color: #734f96; +} + +h2 { + font-size: 24px; + font-weight: 400; + color: #734f96; +} +@media (min-width: 568px) { + h2 { + font-size: 30px; + } +} +h3 { + /* color: #54a23d; */ +} + +/* Mark new-window links */ +a[target="_blank"]:after { + content: url(data:image/png;base64,iVBORw0KGgoAAAANSUhEUgAAAAoAAAAKCAYAAACNMs+9AAAAQElEQVR42qXKwQkAIAxDUUdxtO6/RBQkQZvSi8I/pL4BoGw/XPkh4XigPmsUgh0626AjRsgxHTkUThsG2T/sIlzdTsp52kSS1wAAAABJRU5ErkJggg==); + margin: 0 3px 0 5px; +} + +/* " except in the navbar and buttons*/ +.navbar a[target="_blank"]:after { + content:''; + margin: 0px; +} +.button[target="_blank"]:after { + content:''; + margin: 0px; +} + +/* Hide text for social navbar icons + if not on mobile device*/ +@media (min-width: 758px) { + .navbar .icon-link{ + display: none; + } +} + +blockquote { + border-left: 5px solid #eeeeee; + margin-left: 0; + padding-left: 15px; +} + +blockquote small { + display: block; + font-size: 80%; + line-height: 1.4; +} + +blockquote small:before { + content: '\2014 \00A0' +} + +pre { + overflow: auto; + padding: 0.8rem; + border-radius: 0.2rem; + border: solid 1px rgba(0, 0, 0, 0.1); + background-color: rgba(0, 0, 0, 0.05); + white-space: pre-wrap; +} + +.container { + margin: 0 15px; +} +@media (min-width: 568px) { + .container { + margin: 0 auto; + width: 90%; + max-width: 1200px; + } +} + +.container-flex{ + margin: 0 auto; + width: 90%; + display: flex; + flex-wrap: wrap; +} + +.col-flex { + /* display: table-cell; */ + flex: 45%; + padding-left: 10px; + vertical-align: top; +} + +@media screen and (max-width: 700px) { + .col-flex { + flex: 100%; + flex-direction: column; + } +} + +#navbar-logo { + height: 3em; +} +.navbar-top-align { + margin-top:1em; +} + .col-half { + display: table-cell; + width: 50%; + min-width: 50%; + vertical-align: top; + } + .col-half.second { + padding-left: 6%; + } +.navbar-right .dropdown-menu { + left: 0px; +} + +.masthead { + border-top: solid 1px #ececec; + border-bottom: solid 1px #ececec; + text-align: center; + padding: 20px 12px; +} +@media (min-width: 568px) { + .masthead { + padding-top: 40px; + padding-bottom: 40px; + } +} + +.masthead .container { +} +@media (min-width: 568px) { + .masthead .container { + width: 568px; + margin: 0 auto; + } +} + +.masthead h1 { + font-size: 20px; + font-weight: 400; +} +@media (min-width: 568px) { + .masthead h1 { + font-size: 40px; + margin-bottom: 20px; + } +} + +.masthead .lead { + font-weight: 900; + color: #54a23d; + font-family: 'Lato', sans-serif; + font-size: 16px; + font-weight: 900; +} +@media (min-width: 568px) { + .masthead .lead { + font-size: 26px; + } +} + +.masthead .btn { + margin-top: 0.5em; +} +@media (min-width: 568px) { + .masthead .btn { + font-size: 20px; + } +} + +.col-wide, +.col-narrow { + display: block; +} +@media (min-width: 568px) { + .col-wide { + display: table-cell; + width: 61.8%; + vertical-align: top; + } + .col-narrow { + display: table-cell; + width: 38.2%; + padding-left: 6%; + vertical-align: top; + } +} + +.col-right, +.col-fixed { + display: block; +} + +@media (min-width: 568px) { + .col-right { + /* display: table-cell; */ + width: 61.8%; + vertical-align: top; + margin-left: 380px; + min-height: 500px; + } + .col-fixed { + /* display: table-cell; */ + position: fixed; + width: 350px; + height: 500px; + z-index: 1; /* Stay on top */ + } + .col-fixed .content{ + overflow-y: auto; + overflow-x: hidden; + height: 90%; + width: 100%; + } +} + + +.front-section { + padding: 8px 0; +} +@media (min-width: 568px) { + .front-section { + padding-top: 30px; + padding-bottom: 30px; + display: table; + width: 100%; + } + .front-section h2:first-child { + margin-top: 0; + } +} + +.front-section.shaded { + background-color: #f4f4f4; +} + +.front-section.shaded.purple { + background-color: #f2eef6; +} + + +.faqs dt { + font-weight: 700; +} + +.faqs dd { + color: #777; + font-size: 15px; + margin-left: 0; + margin-bottom: 20px; +} + +.faqs dd pre { + font-size: 0.9rem; +} + +.btn { + display: inline-block; + text-align: center; + vertical-align: middle; + background-color: #3c92d1; + color: #fff; + font-family: 'Lato', sans-serif; + border-radius: 4px; + padding: 15px 30px; +} + +.btn:hover { + background-color: #3889c4; + color: white; +} + +.btn.full-width { + width: 100%; +} + +.search-btn { + display: inline-block; + text-align: center; + vertical-align: middle; + background-color: #3c92d1; + color: #fff; + font-family: 'Lato', sans-serif; + border-radius: 4px; + padding: 5px 7px; +} + +.search-btn:hover { + background-color: #3889c4; + color: white; +} + +.search-box { + width: 85%; + padding: 5px 7px; + color: #777; + font-weight: bold; +} + + +footer .container { + border-top: solid 1px #ececec; + padding: 20px 0 50px; + font-size: 12px; + color: #777; +} + +footer .col-narrow { + text-align: right; +} + +@media (min-width: 568px) { + footer .container { + font-size: 14px; + display: table; + } +} + +footer a { + color: #444; +} + + +.light { + color: #777; +} + +.light a { + color: #444; +} + +.small { + font-size: 70%; +} + +.newsletter h1 { + margin-bottom: 0px; +} + +.aside-note { + color: gray; + /* border-left: 5px solid #734f96; */ + border-left: 5px solid gray; + font-size: 16px; + padding-left: 10px; + margin: 20px 0; +} + +.aside-tip { + border-left: 5px solid #3c92d1; + font-size: 16px; + padding-left: 10px; + margin: 20px 0; +} + +.aside-important { + border-left: 5px solid #c7254e; + font-size: 16px; + padding-left: 10px; + margin: 20px 0; + background-color: #f9f2f4; +} + +.projects-table td{ + + padding: 4px; + +} \ No newline at end of file diff --git a/_site/assets/css/syntax.css b/_site/assets/css/syntax.css new file mode 100644 index 000000000..b3806e885 --- /dev/null +++ b/_site/assets/css/syntax.css @@ -0,0 +1,73 @@ +/* + friendly.css + source: https://github.com/richleland/pygments-css (Unlicense/PD) +*/ +.highlight .hll { background-color: #ffffcc } +.highlight { background: #f0f0f0; } +.highlight .c { color: #60a0b0; font-style: italic } /* Comment */ +.highlight .err { border: 1px solid #FF0000 } /* Error */ +.highlight .k { color: #007020; font-weight: bold } /* Keyword */ +.highlight .o { color: #666666 } /* Operator */ +.highlight .ch { color: #60a0b0; font-style: italic } /* Comment.Hashbang */ +.highlight .cm { color: #60a0b0; font-style: italic } /* Comment.Multiline */ +.highlight .cp { color: #007020 } /* Comment.Preproc */ +.highlight .cpf { color: #60a0b0; font-style: italic } /* Comment.PreprocFile */ +.highlight .c1 { color: #60a0b0; font-style: italic } /* Comment.Single */ +.highlight .cs { color: #60a0b0; background-color: #fff0f0 } /* Comment.Special */ +.highlight .gd { color: #A00000 } /* Generic.Deleted */ +.highlight .ge { font-style: italic } /* Generic.Emph */ +.highlight .gr { color: #FF0000 } /* Generic.Error */ +.highlight .gh { color: #000080; font-weight: bold } /* Generic.Heading */ +.highlight .gi { color: #00A000 } /* Generic.Inserted */ +.highlight .go { color: #888888 } /* Generic.Output */ +.highlight .gp { color: #c65d09; font-weight: bold } /* Generic.Prompt */ +.highlight .gs { font-weight: bold } /* Generic.Strong */ +.highlight .gu { color: #800080; font-weight: bold } /* Generic.Subheading */ +.highlight .gt { color: #0044DD } /* Generic.Traceback */ +.highlight .kc { color: #007020; font-weight: bold } /* Keyword.Constant */ +.highlight .kd { color: #007020; font-weight: bold } /* Keyword.Declaration */ +.highlight .kn { color: #007020; font-weight: bold } /* Keyword.Namespace */ +.highlight .kp { color: #007020 } /* Keyword.Pseudo */ +.highlight .kr { color: #007020; font-weight: bold } /* Keyword.Reserved */ +.highlight .kt { color: #902000 } /* Keyword.Type */ +.highlight .m { color: #40a070 } /* Literal.Number */ +.highlight .s { color: #4070a0 } /* Literal.String */ +.highlight .na { color: #4070a0 } /* Name.Attribute */ +.highlight .nb { color: #007020 } /* Name.Builtin */ +.highlight .nc { color: #0e84b5; font-weight: bold } /* Name.Class */ +.highlight .no { color: #60add5 } /* Name.Constant */ +.highlight .nd { color: #555555; font-weight: bold } /* Name.Decorator */ +.highlight .ni { color: #d55537; font-weight: bold } /* Name.Entity */ +.highlight .ne { color: #007020 } /* Name.Exception */ +.highlight .nf { color: #06287e } /* Name.Function */ +.highlight .nl { color: #002070; font-weight: bold } /* Name.Label */ +.highlight .nn { color: #0e84b5; font-weight: bold } /* Name.Namespace */ +.highlight .nt { color: #062873; font-weight: bold } /* Name.Tag */ +.highlight .nv { color: #bb60d5 } /* Name.Variable */ +.highlight .ow { color: #007020; font-weight: bold } /* Operator.Word */ +.highlight .w { color: #bbbbbb } /* Text.Whitespace */ +.highlight .mb { color: #40a070 } /* Literal.Number.Bin */ +.highlight .mf { color: #40a070 } /* Literal.Number.Float */ +.highlight .mh { color: #40a070 } /* Literal.Number.Hex */ +.highlight .mi { color: #40a070 } /* Literal.Number.Integer */ +.highlight .mo { color: #40a070 } /* Literal.Number.Oct */ +.highlight .sa { color: #4070a0 } /* Literal.String.Affix */ +.highlight .sb { color: #4070a0 } /* Literal.String.Backtick */ +.highlight .sc { color: #4070a0 } /* Literal.String.Char */ +.highlight .dl { color: #4070a0 } /* Literal.String.Delimiter */ +.highlight .sd { color: #4070a0; font-style: italic } /* Literal.String.Doc */ +.highlight .s2 { color: #4070a0 } /* Literal.String.Double */ +.highlight .se { color: #4070a0; font-weight: bold } /* Literal.String.Escape */ +.highlight .sh { color: #4070a0 } /* Literal.String.Heredoc */ +.highlight .si { color: #70a0d0; font-style: italic } /* Literal.String.Interpol */ +.highlight .sx { color: #c65d09 } /* Literal.String.Other */ +.highlight .sr { color: #235388 } /* Literal.String.Regex */ +.highlight .s1 { color: #4070a0 } /* Literal.String.Single */ +.highlight .ss { color: #517918 } /* Literal.String.Symbol */ +.highlight .bp { color: #007020 } /* Name.Builtin.Pseudo */ +.highlight .fm { color: #06287e } /* Name.Function.Magic */ +.highlight .vc { color: #bb60d5 } /* Name.Variable.Class */ +.highlight .vg { color: #bb60d5 } /* Name.Variable.Global */ +.highlight .vi { color: #bb60d5 } /* Name.Variable.Instance */ +.highlight .vm { color: #bb60d5 } /* Name.Variable.Magic */ +.highlight .il { color: #40a070 } /* Literal.Number.Integer.Long */ \ No newline at end of file diff --git a/_site/assets/img/discourse.png b/_site/assets/img/discourse.png new file mode 100644 index 0000000000000000000000000000000000000000..599f68a711f8cef40b063398f4e2793d1561f48d GIT binary patch literal 9544 zcmZ{~Wl&tt6E3{?;)}a17CcyRcS3N7;O_3a!9#Es2pU2H1PD&hzy=BKvbYlnS=<(X z`TcLbAMS^HPSwox%sk!GQ)i@3KZ)9!D)>0mH~;_uUrkj}7XUzkJeQq-n9nJN{hOud z4Bb&qLk<9_PsP2r#(0()ZB=zO0DurS03a#`0JwdwirNPN{P_TY11kVPJog#tRnV>@ z`P_hMqpqR|c>3@C^s_t@0AR6HQTQq`1~THS*F~MORk43 z#N?81prNwOf>cql!Li!%@{F=LY1+g~Sm0RFnJ&_hV=FY_R=^MM7VgFDY75Qwj)%uw z9qvNSz{Zx)@=T%by~P2qrNaN7z(0j8lot%jD49`-XY1Iq*lEnEVZnX?4Ouj8LLpQG zm?NzGZ2eM}i#l0ZaFAc1$%5BP`~)MImIEuOJV6z5LVO}{l1EDZ++6yXISiHqv6scS zDm&c=tf6)hW*r!nOgRbtwI%m@Q718m7U`)13?dRmJ2`-tKG%nsXA$TN}dkz*@q}1?;=%_|b%P%RUZlw2%llcR+4a(KMs3*B3wCtA>3zg52mP>G%}M9-K(8lcgM1orJdZ_76Rq1#p-}g zQ|6kbQx}e4KGGnH^f@lptl-XqT%$qkV2lr!;*Rc%)QKmi>ddJkvuD<>zLrgwBrqco zw)^u`maSu>P@Hgkxp8s|tnKZ&#wwU(n4MUXrQ%r6d>KlZ+!O|e{&H;v#xu7vVLqm* z@z&78-JA)};@e${JgQ&Fn;Kz>pu+!olutR`mV#PQkl$v=*iVCy7T#0?yW}j@Z{nSG zbKKL+4@#;R7}uBM;H&i4;)1B|%Dm0)(pUQN*hWA2Sy<3}vr`zmYZrUf$MFBU90O03 zHpo^lg{UiQ;4clb!kRNRo+UI9*M)xd=?DHi>q zh*AO7CqK^~8wdD=P*I*zCASdTTN|Hjm#|C{sx7P`NfJhDyp&+go{~;4ak_@q2ZptL44d0Z(EV zrX)h!q#TWK@Rv;9;o0%=zoVKdr)nI?c9dg5`(nllss}e6q&6pc{XjnRqaIVMbE;+9 zNNni6Q|CS%8R2KI}vbiStxOz!8|D&!# zkra&O)3}3JIZ7&PP>u$SDB)!7zh%vW-azE?$y;;9$@v$khSpS*`!JH(de{+z{d8dc zlRuQOH*i+6)7Q~vM=W=Ql@{D|OR}{7R@3P)}6C{Ve3%NIZj)NpW{VDEJY6%J|TB_H=ryO-0ldK7a13@Ax@HDN^SQ(jTgmx?gW(v9`W`KQqm!93Wiu zSMOxJIJ&$cqt>pu&Q=lI6@IMIfA|&%oh;7ie8jQJi#-=X^W68SopK_^h7_ZyEb`m~ zYEwgp2R2fzQI~{!dcoWIiEUCFmm4xS#tkpUY2bAkT_#NS7$@UJDW0S31j}8JTmD|8 zle+<@$1Cz6qJ{LnW(wP}&`|u7f}^YFH+j`4_!M35Hj`glK`@Mi^w@UrD8w|*3F z=O_~xHZXjBb^Y>}M5uV*DT69SO@_@`N^X+th-t$Jj!APsAg9Mn+gZafarLf91VNBS zU}&=Pi~$|d7$M4XM@YjQTp7XK7T{3ix$5exRcPSA*vX#8(@~cTz1=tRC5+np4E@^gxSqES&ib` ztZ!l16-Hvlk?BncWgMS2G_&UzC@d#d*Ob)HPepyg?3v!fPJ+A3B58Iw3py}carpdO zo|XRmj;@Jyh9F07XZXC;Q3%hZvi|dig!wn+j?7^Ys=5|R@8JILc0UA*>FXrQ+ke|$ zdw;~t@13LO@Y5VNP-CDvlBPSsOOpDfQ+;Hp6iYl_-X79=_a;&i48kL+@m5+WUR(Ug zRI^!`Y>l{I$yj3>+uBl@k^U%1R88_@RCFG#w_f3&YPQ;PO+F`7kH`w0NkTP|G)rKjZCV{P#3P1ZDkVC zyQ~QISNL5r5jfw|L9Bu;Frym324q{pY~heL)(Un3C&sV8uy9kr^Py(|KC$nJEzE-p zMttNSUuGsxOV8ApZy85REw>b2dctGS`1TT3rb^b9R0bP;DQH5+A#`nygPf2Fx4|HJw7wE_zp0@o8N+Z(?@~p<|1}PJc`NHb7*DT-@Nk{{P3? zCL9WW8vR^wPwxztB0+8ajAtYn|K_)Zr$e`AtKNtTS{+YQYV{zs=+mAinH1I_++448 z>Wdzb`-j=&yMm*ts5)nXddXqx!9ymm--&3SH&fVo?JF!1ksk&l@yUzPNE{_}ny`#N zb(ATWs+EK4>`VW?!ux~XEkDn0dOM|IGp5(abg6IJrL3|_s z=$~3n{?D8`aEJL_F6$V2adCBps0{M}R!B8!*uYDA?PL+pguzxS0p={BC#*7hl$jL2 z&-?1N`9YO^P+|zep&>_cRfUCHKzoltKE@i_WIF_1dS=N(`Z%`0TN1k z0A?NBm*Lc(n1Z`f6Bx4a6hK{AxS(vin*>Tl4H(;o?S=uOeE3aVeZod47FsDN#YfEN z-AuwsCX&`T^(1d?MP-#W$_rf*eG^v~hjdVU9z2~~gD#E!W4}ZVTgD63>r2=*c#&aU zPH`09WM3gE%B10Ghgtsn>`25p%8Bq~(QikZcdFPD=JPMLu5uVB;}V|7K7TC5`1j;D zy;Z~Nl5%{~IOpX^`|$4XNt=~z6~b0}QKmGd>}3sC(KoIvG2PZ;zdpyF#D1+q7zHF1 ze_=-_kTniu{mhprJ}PgQbH_kzmKqD9AMRG!`KoDO@EHSG-l|tu^myTG(k(NBA_7H% z9z`ey<=E6u+wozg2`5{{;`%uhWaB1;VG=`U$GVj2E>VpkH_Q02dr`PF?!EG33(8y6 z`+~J?_wV4Y#SZnW;wmEY;6x_?ea^&<_xoFQUN7DrqkUk~Qk0hc1AY3#KnAFej;5_| zb@gvm)0a>$-Q$A4R1CDdRCsu=!%==T}l9lf-G z&jLDiwt15AePFGC{+s0sbpMqlu>r*xc`=?}Ki5?G&YvWD6fB`(ihXOiMCsX)=m@`) z(7SX*rjlAVKNT_&A^3z+V?<`i+s56jq>}}r+&cE4J`l4LK!ZviKN@Izd@{Ws$c?sM zpnMS{YsrThwEh{8;2?a$#-vcV3=!u+H5~a^pQ*{_3mE_fQ`PC8 zxQd_&Ajas`$Ub~-JrDp8`FsenHc0I)1-($WkCa@5INlPUB+@n|(Xvml{<|zeL@#nu zETkl^%&BpsB1a!Adg3PHLlG4y%Ur%46+KLAzaJuVe@uEzDco*&4}V#*dauBMxb&IN za?5T9oG_jU5LEDNdy&@3S5hLv!eo>X$)e^)3N_sGYG6U*HXKp4&CUs;kTc`s8?_9* zA0Rmq>%u{A6BVJbBNFTTD7`WcXmg@)gsRgZ^+G3MtTk!+;vQuqLTvkosZp{1%ax7E;c^k> z*I+5owmR!H1))mCpgxjID)R-DN#E6k0DeQTA&>+Q28HUvGeWpv(Yt{{B46b{^{%Y1 zl~icKpw{1*3d?vpWw@0m5&KN&ZlQ$bX262jx&~E@O7b^_A5bg?Oy*KK*VC#9b7Bc^ zu{XG!D~lQGZvsyl%`j*ktpTZDaoQJ4$Yi;XWTme1Q0}pjF4W64#+vjFWp9A9{#3x; zqNDYc(5N8bwQ~5tBcz*kS_zny`gJ*j{X7;n$H9H)-sez+!>apL;0K}Qzvr6~*+e)% zHISPWt+kx+D1V46R&xzaSoy&)4h_4J_yWb?{9pc^6Kf8ZB&*SalmmZ6$5*)WRsMFK z!?i)Kj;W+osQrS_H#gVAtEZ=anyAm#b+rvLKuF@k2c~>k0Bw9-ywOJk8BQbA@G-*O zs585F2EDQ2`Z9zz-MiW`1Yvaz3RmCJh!$^bzN2cg`n$A;f*hJT+d8_lcI;fGdW=hP zHoMc9vCe~mB;E$YyLN6w=5Jc*bmol$KH}5p%x~7L6re2MaYlb%y+RM;H3~e=Dq%(d zAzsuBN(T5B1qDN4EH4PLnEkFCi9^rf?*V`kW-0NH7*z7%7veq6Wok7(NxR%9z`n9i zWZ@^veIh6YfP3M@c0=$z=?`#2_YFuH;JedkHe`~ACdpmwUbmaNhFkFBjs?h-Tg!Cu zICOP<2U%AuG38z#YT1|S>>xu)d$A6+F40=&GNL*yz}jQHVi{M`hz-uFJ~vOnfg~T^ zq4iU3RzPJVj-n1@|4|>bKXgxc&G3ZE!{!@B%1(9SxC$DHtv^n2?B%uNb#`aag{9!5 zc%_k|8ZMyU%a3~y2m3mxS^Fmy5cTK#o3D;oO+zJkaG=+_=Rb)ZVdKh(!na&lU^4PS zvZ0^Rs(>bN7>;4!&36o>CC$Sfq2GE-W!iuYWP8_2l1U8(&=Xg8XyKS5%~cs&yd@NN)d%&T)3NlLWf}Jz0f7tUKWT3kT<@>q zN7D5ypKr2Y0DyFzl`hlh5j+z23KebVEvS)M@D;M{;|_@W?g3jmKvb6ik5dtpBI`>u z9(n43-~rYyBmx_ax$*cSFbTU8hyjV(*rr#81>I87+8sPvx&S;S(RbgxM0!4tSK@3c zY@DD^ObvnBgW@EZ(4}#I5NElhyY(uyR^9U05G)k6e*RH*_nMLR>#fhSsnb_IAVN=c z&v;9sDCUdHzL^>@>RUy*$f2w;jd^T{TW*aIqg%(zOf(-srh6E~NBFz$pHyyOR4rF1waZ#>OQ+j}{ zUp$zO1XXUv&i-G7l4?>_5_KPKZsl-F!VuS-!K%tHt62+={O`2Ke@Rg}Po3EY=U`dr zf){rg6?ZK2Gsd!FOlFQtp~^6dX{;G2zeUZTpFXuWO)ffpl+Yg${>bChofz@zGsDS}{H*@|@iwUJk% z6tUN=9NY$mGNONm@8tE+j7W1fQ7fwyKBOl>RBbbTGuWb$cjHAgSILmx&*YAwhbuPW z)C}dAL<)}IdfF_+W?Hog2D|$#7{6m&&|^0&x4#}=xXZI8o#?=J zlo#L5kj;BcuOYRv&u3U6h|Mx(;l3N~mA|fMg`K-wc4n6?ty}pV&b9QC4p^J)z)H!L zp?kwe>4gRi+C5-L)2@wM(UPJ|r#C*+QjxwM*L9a)FJxRNb&Hiu&5+!{K~CjmasA z(;hcGQrzT9mfBE2a{*3$%r7mX{O>s<(7HK@u%0&xmKZ0xg^P<_2Q96LQPPk1czj?h z8=rrBuA%o`E&j^a48qI95<1a!%BmvW@=~1&)r+HAQO&>!RReuy_O1++TFY0Eu~35b z7L4XP^wU|o5}D}k!kA{4CHwevN*DC%DBQ)B7TKCgKcQ&+Mbf5R58NqwtgNwGu_ZgB z8uI;Xh{7wi01cd@@1JwVlV|>*$pM>|!&1V5NqiFPa6H9@Q!ef|DFPn_2Cm(TJt`g5 zL(?+SxAe$~E^dS_ z0v47#?Ck7Mi1J!v!HUxiqngIhcPv@_hBPLdaQ(rL+cGoGi8`GKjUo|Z8fET|OPI>! zra)_Xp`T_a49PO~j96IenMwA~np1W3QDok$u@%Qy{(5R4IVGgvv8+SlxYn zouGKm$MkPLoTb*G{T*^~Tzt^YR5$y~)l5Z#7f-s@&(|vye-l67TZ?-AC5G(a2d{A~ z&q>OIN9muu(eG1yLoH7JkOX*K8^-w;1Sm@8%b>2S7^@oN`-YP-{np~8* zJL>`QR4NKHKGs)NR8I>yW)6j*=V}q^lo6JdFPXdF*oZpl^$1NQz=GmJXy3Db^SQLx&4YGfm z+*Ekcf14P{OK_O|Y^13?_U#Q+opd7U1-kwUe6=qXpUjg?dtoA0_C+z1K;&3&-nV0u zpZAX?J*bU{q8mE0y_Ia52AbwTiu$DJ}0; z%8Y;iQk&P=MO$A?m43P=GE@xYDq7Er5C^Cp#Z`)t8FdVQ^Y>o>5WmqCcl4@FlW}4S@~5f<2ab z9kJWop?AjQo%X)0&o3$2|bKN9XV}f zC9xg7+qXBqY$#k72AP%TdaU?ZJ&7DRBoY!w>Ya5b^@+l(_=t%z2e7dUZhW$T5Q~oX z_;YdNIb3Ii9XTlA{Ol#0(E5_6rxDYYh1|?49a4(H*D+}B3tjWmPN@s&=g>OY~ zkf7#p(TykB>-ZY6_83XDSbIyXK=8JlS(2+*ZfD#-}*_ ziSnEr^2VnhR49cdD@3Q9wYj@R1ZO13YP<2$UyY4lhmtV~-Ltj5f742p&je2EKRI0t zD%0#UFkE_x4qLNId)a-B1Ftqqq*73l8qL(Q->3HKuS*F-nl89Dp^XyW$r1 zWyF6qbJCpiTpX#Nqu6w7#a7uz)>HfLYj2o*GxQn49>Yj5ws?wH^<1jj@w(_IZC~va za3C&C^+}KX`|KH=V%hT%Z&+je^WCr&A`uDHBI@XY+l1I4T)R#wSG*HfIag9mg+CdG zY3W4Ks@-c;auEfGhT4+#NM1N!4b%^1$Zv-bO9(a(Lzqcb@Gr^d{imB@BnkL`2#Ltq zFB3HOiN(|llf3qIu$yTWbAfA`VV)DVQ54*j{H8=#8xu@^7jr- zJ>qSIK!6Z#$_V(ntV&>s)5%?dPR967`X%D8RNJhRE&B2YR~TI{OT>(d*Xk*#>1#js z5MiV*0}iBiXuRyUAz)a}k@Uc#>u52^m>OZIEW{DR}sH<^u&Ubh}?5_o|D^}1& zik*!BjE)ZZcXeW#O6WZeXAR11-o^2x+zgltO&x`jjNE8VZ(++i@x?sLa_Wb)BJ-&tvL0t1L&zB>dKhBUf?pa7QZVtNf zt!Wkt*dwp(4=E0SFW7Yf37zJ<2>9|3&Yvj59@0w^A3jdb6z8u)?1Ri5;=)&7+H?? z{G4eDKO7@3^X0(@67SqR-K}l)(DL(WY{f(Rd;a<8&{GeL4~ij%=|~)u?3$wZUYhUE5!MW4a&_L_Kh8}#+{LU-zdWH@#6B)Oqe7D=3V68tdRrKJ07Yqwtm ziYUG{hvM^EB8?=sZybS+%FDP{JDT(xW*@HfIBGEcfR03^uZ4wuSNP^B7G*fhK4C5g z4U`z$1m&CMEv#(4?Mh+NA~zW$skq>=?}!XKei0|JQNP@0Elx}?`EDV1C@afVA__y- zU_-y$O~uXhX-b(Y652R~W&fbt?{Ond-=d@Zlh!ygiZ9S#yc{+Fi%m%OeSrkl=bYk= z@BIqL+~oQBQsMSm0$6w}L#yA5kVF4?$2atk#xC-PS6-#~J@kEI-BEjiXcs|>DOPx3 z56VhAB0q>Q#htwUTbmBvJ(-!Yxutr_vO1NLpAfX6)|P4P2ABUQzwnO40lQ1s`>lI? zgtyTY=(Ti!y#}yBTSaed$ zOr@{sjJ3+ngqU>QnC3=+G?%!8$49U8<*SGddd+n7NXLwg%zycs{y5-8tSlU|`46}ri^em~>#5QQS5wkNN3-_q zBDMAq7fKX(2RxsU8TlBA`^}c=1Ya>`Xp{UO@?Aljv~tLq`Wr>WsxdwdN>9m&R)WTc zUF=^4mVl+DXhB1P-rYuvm=NwtU{C9&Fz&jJz-2qI-cgVz@n0aLyuM^itmN?XpQON} z8_ami3s#q<==&-giq!C~e0+bRt7ckRJv*EdWfA>jQnZIPx~*;rtoxvBVXT)ijWrOC z`0__RrwYj4GZ&=I2#D(VO~DP*-M?}0C)kA9QQ>%y z&{mx~2U%#HN|@;{Av<1iuba@!jHq%25ebQ?f-i;t5>9MpxFnQDeM_jrxJjrZOZHLH zW&Q^@83?(>Bu75RHjcTnWFs6 zoB*bT;*~oR?8kmnfmshEMyk-E^Cp!YCEsmi23n2f*KIl1GpX^w8Mi|I3&HjiRtE!C0ntl>h! z&k3!5>JEiTVLB7`dX?pWV2HZZ$wykGC8mYam+eiO{7~ zk`rX{vltb6+wA)6@WvBLa)2MN_3diqGx> x>hlYT3-O8b332f~r+fyZIe-2yfV-!ivqSLz8^DtO()1YscwTmjHS$*P{y*T)`riNm literal 0 HcmV?d00001 diff --git a/_site/assets/img/fortran-logo.svg b/_site/assets/img/fortran-logo.svg new file mode 100644 index 000000000..8cb9dc716 --- /dev/null +++ b/_site/assets/img/fortran-logo.svg @@ -0,0 +1,98 @@ + + + + + + + + + + + + + + + image/svg+xml + + + + + + + + + + diff --git a/_site/assets/img/fortran_logo_128x128.png b/_site/assets/img/fortran_logo_128x128.png new file mode 100644 index 0000000000000000000000000000000000000000..f40293f5510e71602d9dee8fde3872db94882c69 GIT binary patch literal 2977 zcmV;S3tsezP)l#SnSfPW z9qmwB9sw-~l(DrIl%g}$B!dnE!q^IkL@iEHB99~>4?!Tw4SC&r_wGYJGd1%rnD_=5@&z!G0Vx2|0B|ePNMK9=wF2-n z;5Y<6XAtEfVE5|M`A4G-<Z<(bP2~Os36ZOw0r@Dq10mh&U<)+iY^Y{M?&!t0D=| zZv!kWTyq15>q!9j0&qo=sKRnW0@x}{bLr}`1&8``VAuxu^}T;i3$z4($H3-8-FT;B zLf}Qsa6Pu{_1U%I91xZPil(i-9gM#UU`SN*6n1eET>P~7jrs5O^}{|ZXhqZ47lHA2 zpl*IFkqeXUE}HhjBYpj_mmEN_MTP5^3t*9z$`m#u*z)4iIgbNObho?5vV2it&I)z& z;{b+<6AC``?yK0gv%B5h8lY(U`XT_&$ke5<5r&Bq3Vv9#ui~x!U3Xo@;=*;enZPap znl0iKb`j))-MON4?w-yYuQ0%)(^sdvgz;af3SYc(vZW<>{hGIbRoA}ZinjolFqS~w z{CFnU?be>{yrClpXlvp77^;yc-U$MHTye>qPk~N3KwI;!y7}>s#)SDq`#%h5?bs3A zbp#O_VCq8?a7W=di}WeN;oXvhD0^vdq=yGXjO9J|=G>~*9KgjNgnIfD35^3Yfwm$* z2=)N29);a7A!YyoUp!?)9)QurdKC7Pzi8^35!}?wyQq~Yh;Z@ma3R=uY8?t1gka-2 z0}7~xD99+_0%AC|3I!P>IBOlbt4K`JIDjN-6$&y^I8?W9BBNPy^UGe^i)}COgW=Nw z0EWj6my5$~XwVG}hEIp#al@NzAR{XoIk}k_`_19dba{=B&;IOh2nNj__Zwa}T)ed* zRMTB>>#di9aRyJ@c>sXNr-Sp>J~Pejg6?s{Cg=gy2lM)vVr7uFH$p-kecc1 zh!qQ1rqnbA8ta<@pyO|EWagw|=Hki79i3&Bgez#MZ$_vW1B9b7QZlnsFmmi*6x^JP z8*Uv5&F$P)cCu+(7r(5-#%Ib<^Hn{S1ZiA6=STVO3cOOh6H9)v2|KoyBiIt6menn! z^Y$9+oAICbqMqL7XzFVlv3<({6hHbJsw=*vmeU3DiJRw7hc$sE<~e`51{cfIwmy z000{NO?YGDzo}&aaDV{<36=x2^I3T{4u5olS_ZuVOta^A^>}CJYadcepf>=zowAr1 zR2@ExQ^(GeY9Kd20^ffCzz6RfCQYB*0ErHDy8wBwg%Hlp0|pLC!;D4Whd0^i*rsV5 zy5a8f+d~Jc@Q>$r^(%hOSM@kkeF1}p4TxH6B#;}x>19A}UN(k~3a`UT_jENyI2`@t z6qx~35zq$%u1S@i#;MA$q^HpnDg4wHGeimR4t!0eT^OXu54_)m>_^Ev?Qd1N6ez@^frUtL|cg<^T?^0w8bPP}|a~ zO;iIo)d9l_a*&ywVq1ENn*&e_=z$48xZc+E{56d*P5Z9~xdEKW@G;lm<~#CjP16jS zxLn(4Ynp%)4B)ULAZX`haAlXC)&uI|b=kDagsqfXhYx43I)^00|xMtSx4PzX=WgCZLBg_qxZ85!YUW zn{La)xJjd8YKd2?h}$z}jP*I`q@^iwL9Ka%syJKrPK6>|v#cG@jy#XY_c;v<^{mUM**}8T^ zZUAZRKv4v)uWQ67dyiYE#lespKo*e}0qq>vMZ0>JU630L{C(A|Gvo%4g%vpfK(}y%UBs^eEXrD_ z7H_f(asya(qppTql>=N-Ie=UoTn7MJ2bIJ#^ahZGRdoQnX6aH9wzY;`ay$PFOtN!8rS0O3Gy zfNs9PX-QmF1cU{>0VLfhk588pH{KvOK%}2r?F*^}pJNSj17r`8^I@jkylg3P;|)>+ z3>=(>TfTR#l-Of#%Eh4JG#_M+B}fdw7%=u*BQS4CAq=maB7nO%e);s>$iHzY$;TgJ z1y)qJF6xEaIA=)7@WHKX@c4AN4GnHxgEvWs;nm?wG2lxw;7vA=n&HFH(OF0vVBZq$ z{!0xwU3CHenufMjLz;2f--O2cW`sf}ni^UV41^G94x+g!05fR9U)z`vQ^PEIS-y4h zb+~8F?N)@6LP~}Y1sT469aDAqEY?2$h9pJKfdhzo;CnnS&7PcQ&o_gK3332Yk9y>B zxYAZUo>MpYxd3XTjS`Pbt+`wYQFE;2T%a=ADDn8TB*b_EhT~iS6;a2rXaJ^@a3#Qa z0%oFuGl+6(Aqpb6_>hNy-PAf1M1;&;e0AykqhLs!h4B>aRIDs}xRL{aFxe~AY7{mj zuo-CU3*aL7cK{($K?*wwLNhl3orYulyl zAPCd7wEdqB1FSAva0tLU5=jc%U<`jME}Px44C)oF9h&ZX3cyL*RVnPEnw!Qmoi|)z zfMu`Gt`#Qk0}%fm;fY6(3--YB(x3Y~Z|u_ExvFg5`w(KWeYzBOAb>|#l+N9A_4aPZ zWbdnZYyY>$-0fw+B>B=5Hn4P6$-F;yx1+}%k5wgepMYS?A?Ri75I-KmZF@mCSpgw;zSokGpu<`iUkJTL9!*B26KiYGLC3Rb}(u z@9T$Q&CA+bvF+r{6u$`cQSQ}^w-S_;q1!1jh)$frUMTHx#142&% z?8i{Wf>Q_r*aFkFv~wd*I7B>@r|6!w!-VOY#e|pvAV1PLim0f7z-DOXrs97tsE#Cn zC1bf3{%GAuS4i9?1RD>a0Kjkn=>Srpii>Co0jL8|1BOZne9o9CN66f@vh3lg$8-J< XPr30*f5xk_00000NkvXXu0mjf#~yoW literal 0 HcmV?d00001 diff --git a/_site/assets/img/fortran_logo_256x256.png b/_site/assets/img/fortran_logo_256x256.png new file mode 100644 index 0000000000000000000000000000000000000000..e41a199fb6d52033fd95d4c0c447c5668a0a7b16 GIT binary patch literal 5990 zcmZ8_cRbba`~Uqq9FCQhk?q)TBQi5`;*^n)gt9v_Q$|Kv#|Rn6mKmWkvw9;V$CeR^ z>=79enc4ha-k-%yzbX^Kkw_l*6Y5m`+A|Tt3gA_MhO6*(bB{k006;52%yN| zhnZWxE&QNx(Y)&p&)+%wL9FwG_hI6NC)Z4#+nRVc_Q&~fEg)#Y*LA_h#6Rk?;~k#qUoCQP^Eim~Z)BmLN_WKv2&NPr^tPt50@ z39nPl9Ec&lXX4`@zr`z!?g}BFdm3VF*AjO9dwh@_S`ke0#pxj_UTNnSWS~UUj2Xpw zL?64nR zp=5Xo%~E1?4KrVK{-c&dPiB$y)|WHX+j+-5a@tLeS6CdMG_0zqp0>#hcLz3>C1zFc+Bc(S<(CGQD4#H4J0jh5vK z(fCRep7t=e{0B!V4^$$ugXOs>Rr|CY@&sc`I`9WJpbdxO-kS~ouV-dTS5oM>EP zAs5%J#akx#TXfI%ZdQ@$bV-Yh?Xl+7 zh<{~bjJp=%oAcdxFDW8|eJVA$@ao%Yhm5LaS z>gn2#vAD>a#o6l=-s$;PvX{N9TB3yGbArYPsa=bojMFq$ItE|EJJ0ntM+Fr7u2iVE zsJM;<<1P2Q$SnUb`A_VL-<+o{pyvqS$zmO`rNu_?J^HlS{)xpR{rU6EkTdiu9%n1riQ z>nbz4V!HR(k`=h@*6#>_h@>`Nw9?I!gCLsQ_)my%665?{b*yK+?eA|y@;VTY#Qa1v zv@-!KV1SvqT}VP77ag+ifT6^-(X0qUIhr0^Fni(J!_Y7x)=&{`Lk(W^VVh2FYwTO8 zn;vv%gC^-Cp=3t z9qPfJwKolE(3Ox&B*Nh6>IyD{4k={+MYb1y>tuf(#+X#-wBUFG%;Y4}q>))Q z&lEQ)cU0C!2m3=cy$n5~@G@69{E;{6Li+Qg zoQHb|f=|&~r16oZ?3^H5jLckHg#1R=!eq_n7Ry{$Ux1kNb!6=?$CzxV#Q9gItnGOP zIH`g>lz?=k>-W)p5$#2Z_rmzVSt-WG$r?uT>8G^SlRmxK>XvS=7TP^!KW+KNTBB_9p24sCpxAF~W3|I5{+_s3`Iuc=I&Y+B5}b3?s8`u>a3BkQXr z`BUyD9{l1Ts{qJ;)@NP+ccn3(a8+xpaaWQ{bUcFF&xdNtXSZfq;hw7p1c;*PyZHnR z^X0N#6qlJr;9|fD*{thr4-WB~PvD;3lkD7oO+Bb9!X32hO*RC%KH4P|vb#98?I6MS znx4V40;T@&FrzDxwItDnxe9Dl028yYIOO0`ax)W_MLfTt(3rEW+ysCe71tqp;cK-@ zKIs%K9@&t0yCIskL665!}{MVoA?@?SXUpVRdMrt*tS}Wgq!=d8KFqPMWXrrcV9+~UTezfC|h!C6d0GlK?c@9Oh@X>7-5aJBt-sd~n zqHH195wE^foVmx$a}^2OC#PYEvknpics@M6q%s+^L@HHjU#?<=xT2XG2Of#xyL4K0 zLu#j)0>-}0?d9Y~-G}SXIuRA$PntiS9p+WC6_ zHv{m^8y{0PK7X!p`Evfep12{W#>X^24cDd2U8((}N<$4T5oUZh>Z?-fVvQC~(psBW zP)CB;TJYS#HOx}9ZBFp})VDm&7R&z$u92g zrWMYEy=Qsdm%X^}LtxC3oUUiRg?k;H^6QUZZYW7-Cnb7t*XxnL;3j2dtSRet3u|U& zJ8$=a&ts-_0|z-g%y`>m-v9`4mHX)G#iOg-K^Odo;xut$pjSshNJVItUsi#c-%W}c z#6^~aaI+{lW8N17E(ZE;7yl0p9LY$2WP%f1n+d>5v?F-_|0=M$NW!Ci9uBF@z|MdF z&*T})YU#mC|uSKWuPU!|eXdy~?2Wm|9j zs!CrPz{fSle*39aohPJwXMbq_J8BNlNMOqf&d@V z81+2{U#$sGjo!&sK;C_h1opC`W!CwpamNojt`5<6qL-&{>SiAdFWW2dIPHvwS+`#n z(NeU6?62=g0k8xo@HI^CGOG;)$J*fIlZL;4REiZ5ck%FcLQ!yvwVl2Nb3vR*^XXjn zblu@H?`1%bU1DHSjuk(bM!8RMD zPyrN8K<#}9Q%R2}sjL9o^LIFj^c*#}Xxbd!LD0-@(&M?(07aX9H>cfU(@#2zu$*5G zqK;iMYN*OiS6fC(6-foKxz+y53a%z9=QAtfx5`2G@b&ptb1=X{1)eeC8NDD)OEF;Y zL9Jg@fnLNxn9}HoI$$Hf3VWA9OrMdKYm{}|XK z*G*vCun<{h+R|+}VYwA)mbNNECmfKNBC>Ti7Q7g20*elCG=b!yDhI&Z@8HO2=YMoC zv$4F@7-$D|Y9G{Z-PU|Z4`>nb@IL)Tz?=HacxQ;)p#I!{V>(K5Lk-sQ;t6WlY0+@4 zU}FPMUfxeF)ugFz&JGTAmNXH z?%&#T0KDzZ$X7(Xp=g-eXJ$my94y=|#6^t>oy_~Lk;Mv_nFC|-de($@S#K2E^B;te z)VTgK%e>NpJvZNlfHThfhWP||O-vCXzKm*7r->%=&3qYH z&bTG%s?GbQ!5&?)HL#_YM)>|{aP2YiYua4C>O@G@Tip+@mawMoLW=k5cpr=%r+h{b z*dS8rBi7rAG;qQQ=nu0BZQNb??~>sADKN(82bFgm{W%`GOw~rgvSa@|(TKG#s9MEm{gb1?_WYr1U$|Q51mVh)F0!3Ix)nYgu8G;^)bRy* zPhepzjIfs>Xijgj6J+?H2SWKRa1`JOh{b36^vs zi}}HL#&^uH6Zjneszn!n7_gAOkF>_h6Del;cLjL{hw7M(-591c_TA@V5H z4cQrTv^~xZP{D8He1v~Urc(H>17*r=T8q*+E^5mUVZ!Mxh-tkyiUjnF z|Sz^lJ$`DMAunsM!RdjfTyxwrRG#5r=ObGUddSNrywVN!1n9g+{&vs^Z9fZdDM)n&n5ae&Jbc~nCP0a^Jdmn)!_@f-u@t4 zcD~@O1#;`#F41b5^#eHTN%`@vXAat;(Mp;#rnJuco7q`=oNl&ZY?e(e;BTH76aAZv z^Rp$20ZlQX2Pd&e{adcMiP-xhV9F?2Q|~Qr>%duCM_uJdl)F;NSjC8S~OYtco zG3X^VqX?QepysXHXY&^ikMPLdxqFxYe0^ik85Y}b9~92O&)Yg|tXl2uafzz@r{H7J zQXiX7GErHev-18^?33$4q(2*D7VJ;;#p=3o(`{<(P*1sID)tFwU?!UDRBiwJgRo+g zj0Y`$&lGpQ_UdD-o9rHhMi-?5qkp4!%p8Z>Y4es|O<1Py=H3mpejnB<@W0+*TgZ~pn<$xd>v&(BN|O~rM7tzg=U`>kyXqW|k(CDJ8zdrZ5cT#>-+OkugXqVa zB8?AsvANi^WzdRiCi%Is-#s_zTWbWTguW+EBxCr_>jxp4$$sztn0@t^yAD9Suq+x^f7qJA>Gv+|bR zz*kFig4C*_OAITgL^|`*RsG8G%)&rp5#{R-fUNevrs=xbKlmaZ7aIKiq114(K^{{7 zi-9b?HTwrd_9uluQxFP6oBJyfygy}#(l>!XtXm;oEFQxu*^H+q>AaJffWk=gj6s#= wV3i?_}MZtor*?vVqnYr5F?YF0u255Pdu$p8QV literal 0 HcmV?d00001 diff --git a/_site/assets/img/fortran_logo_512x512.png b/_site/assets/img/fortran_logo_512x512.png new file mode 100644 index 0000000000000000000000000000000000000000..f3adfe7f06ca665ee2bbb09b68ba9d25526b66bd GIT binary patch literal 12591 zcmaKScUV+SvuDo`1w=#;P(fY=Ndf|5AdaX=2FX#7Ad*2Cau^W>B}zuJ+90069_TC+J*M!AUw^)6R=UXe|)#Y2!PCbbvCB=5HG%y%qrXP`t2`SWk zRqQ1pn7+6{Et`$FIIXbzmp)ARzVDLxNPFWU*$-1SosU=k!Lj`lmQm{L;+})gT|4|P zi{+S8a<8uJDySLnUi<5(t~I{<{glCs)=Yv&;c4lGo?bf{_MS2Ih)`wWHsy%xKhE`X z#*uyviMp<-DJ+;9K^O5y_S}@95b*nQMV3U?O{e@zwqlRS*ZhbDT@#zq^vVKb`Fh`I z=jqb+88LgEn2|42-Br{oO7E1c-&FR8j*kz2bkbqAPJcluxGd0Px>8DvQ!NgUmUq`F z;b$V$hgI&xXr{OFJ}R21t0UM?`QEYO;Cts_qIf0iuHuIa<^^N?X~ znM}`Q(!!Y?)A`qgvz`w11eM44QL|||IbW>|t}k6P+4zUYOQz>UI4#~01zxf9TfB{8 zxt>&CxEVIh5&!NT1^({K`+q2#I^x!7h4U7_N;|(Q-n=}J{T+J+U|0uaY8s6e_dC!0 z_Nm#K))~bURnvV%f9vb}WAmtQJJomHLB}y9T>vkH0&o<&`aZCQ$%R03~08+T3N1*DJpJtS-LQ{DATKfcTYN$ zE1V1KF`A0uS8BS5K=y@}Tpj7bKM{#H^(!adP!GE8t89`OwFK=H=NNP*SGIWS^(-Mo zx#M*H`LW!`QZYR<?7|YJgADqsvLTI9X1l4SN=V-Icna2B*%Cfk{|q(`!kn5=V$JPW0$R6d}Uw3n81WBH&>rnR;U4Vq}g7UPDp@Q-d06bJ8+{;sCJ z7RJ-nup-pv!7sQ?1lqpsQQSCMSSX!23?#4;ofxHR%E%fIlVdyM7_<@WR2Wx zqUJ9b(Nd}0z)*DSmF$k^zO(EDWOcU#;2O-XMVaq-&j~~o;U@v^(X6mS?X33s)Y>5-X<^rt0&2hCK1KcXC2;L z1SzY{X2Q#FO6~SjO%uC5ih8VMGOa}v{FqLbpZ3&Z0>Hjmrm`X^)N5rr-W)6He$Z39 zzJ6ZytLc7ac$dQpbVh!k4_=ziP%)U3N7jMsiMI=Lg`@R2t(5pStcU=OROn~x`TV@4 z9Vsg=!?JXe34+jc@O;OZMB8DHbjJrtvY2FFsrZxaYAZf;x7OdtXishLiwD@z>w_hRbFG86SaS^*%ZYRg~$BT{=tZ0|4n_pQ+$sL`vZq z8p_oPtt6pCkML@?FM|N2pqZcjMEUea1o~{rsPNNh*T#Bn{_NJ7o4LabiBg!GZB$z= zRnNxUxgZvXE}CkQXk>`lA^}EhB_zsO#12INj8itzn~&f6Q97+-)i=9Ui~<2EST~a~ z!d8Kw*C?^;+}zFdAOV+a&@d+Aiv_Igjs@$@(l>|>Q)uyF%e#Cab_IZM5238xB~Q(c z&?4(?GhIIOMVbV9a;CZci$A@-`|LU8zm4~rP7u#$&|}N#3Y|m&oVQKedB^OFdnoBT z;%`pIYCqkJ4FeHjr3A0$A8Z6Mtv&E$PCm_mi>_H24|7_O2_*u+xl^W9aZYz{S>l5E z_LF4cEhDS-pj+c`mTH?@3ya&v$3TXYTi{a?DptV6TcPDpf$9)|NZmT4&bqf(NvLXp z!rY@RdY-khU*3`cFuqO8d@^Vt_S24KfVOEtXlCKzUt|9BIhIxYQ~*fl^F9h-UO(_K z=e;<8liG^3$-UT$X&(jb@mI{BX`Pxm?=MDV->h@f`y1ohH~U9$3USj}rK;&9d6x5S zl~fj_hz}9C>^S;O6>b>Aw7i>{nfXuf++Fw8KKyid`)pWh1`M1i(fq|7hh*lqn^f*6 zQszGE^%SIu7{)B5r_R8ycS?Fzm#l5aZ=cd15RRQW zHjzD|;P9{8df`_>ZbA1#K3rS=^_BR$vk5VyKO%nDipX7hd&{uo?YaH>*evx|dKUnO zeRh6U^B+Td=Cnv>E9jD?dJ056diW@D0-J_jf$CSTEcR!&<3$FsQ~-C%c6&Hcx52cW zz{qa)r!#t?kj;e5y-R5e=z9+YXUU2TZJ9z&G0wYD=AC=rx{``}(GyILuN$8OfRT;; zm?65iiX)k@ni;z$+hfr{2BncIRo!xCcTWlqH|pf@?S!@^ z_d#gawK3H0==gMocTtO-h7w7L+R^TPtthI$W$uqwspR%~lPQg%eL z>Mp9NW#7?a6+kQe!qDM1B3Yq`n*G7`R8qeN;o)h^?B(#$X;Rz>9ZoT@rBSP=D*Tv> zcxXJ55@pLoBXpo!7r##iFeHL4Nn=~fBa5gMm@cWrb>w&*XVj5dH%(ghW6Lst^*P~9ASEzCkgwLa4?WRnBQq|@);%1DoqKn3c#!)re9E@glU(-*R}XUw9k~Umu;q_kmK{T) zhF}ldpc_=>2}Z@l+m4Su%BR=o4F5`kb5f+5=QW>jxCvNgRx3e;$Z<9JYlX#4--3eW zO!fVKUAf0}@D7|h$7qt}-ZCtG{J<4Qsw{XCZvq8PTk?{$Th7E_1}?^KT34K8%84-c zhMA!Ayq6G9r~ElmW@A4srVJ4QQfR#%!kIa?hW(nmoNL1%e0)pV{p9GA(Sd_K0OoJj7 z*y-e5-?Vy!JQhoHqUT^iJ;tDhUhBI&s$QyN%SrRI`>oo2-mOL?2NIpjHC;(oz^V$T z3Fa~-&h3=qXSyGr6wb{naak!N*n=BM{W5>S*_4b_}n)9%6Ca5=54 ziv2kC#q6M5f?zIQp1~abT<+shKYe9oAvPqD-Bwi_E%eL>2SBpiP#AMmt zqu_;^J5L{iODQ&L{%1S9)B}@T)spuIBh+tZ4rAF;erxj-7>>T*$kSW@c*agHT&(+P z&)B3>(`mJ`qhD&*EtaL_Zb`jB)BID|SR^%Q=vFInmghdLZn_N_2F#H)Zt%A zA2me-X|g((Txv;&i;Lo3E^Q#;J-DaP{>piDJ-BwG+0N&l$AxR(u@_iXhjm5PEB((B z>`w6x%)UCu?C`t6eVJ@aZE`8i;K5zu;`?I0H6pberOO9OJTZ7jW|DyXV5^b!tdZni zjhOvV@6GzXjZm#IEc1!ecToY^P$k|w2ann6C_h*RS?fIOYU%dIwp!LqnG;r^y&?)`_XjXG@ zjKr8bHp6y%p1Ef6m4APUcPZgkwhA3Cpj6X+8-E`j(V>uXO&^b^#rT>(mG0B2gZiy^ zNZtdCUBi0F)xZ!8C$_?TW8^$b5C7r#a{oZjFA-{PauP5A2Zdv^xVzRAbBlzAy5PL%dhhaBmjANn7?w^QPyjYr!eCid2r#0dAjv~4 zfzsCV-j4nU?1e}Hh2MyZ38Xj(G9Q>)>;u`s}C_>RjM*_mr@zi7YaL?9S0+(l} zmw&dB)L*+w2V}xa4Cp}01zs;~)U+3Y1zU!#4)GPd3%Pg#aL+b3&v)+5Z7pfJXmw%f zB2ObEbSNMoIhNd`g9r2!`n^Oi;PCV$D-__gE0icz*gE*lH7KBRg%gB*rUfcoEVVNv z;w!Z=2CW#T6o3iuOEg=g$)?-dUpT>QSTc;I^1FcW=b1$L21H#-=ARwNJNgob8sdV~ zUh}*`(LXV9jE5%M2S+j;1~U%0L>-1obee}8j@3En^(0C?wy8{w9(*wN=g35dYd3rxtTx%F+HmRKc5U6~PN6|2MF5C7&+je0lqJ9X2 z^83Tx#=@Eq;Liy-jZc7p=tjv>g@W_L2CcZubbwA^pXfUb=IcLA3Ts1950F8mARwvn zz@nHyZtsW2UAlone=oJ%aj!qvJvS&Y0XeH@JbEtUzVg)vni&}~W1sB(Tt*fbcz6$m zIqd;(PjzdbMQHLF%!rW61;HiSF8~@He({570y!tbxAg}s8sLklXvFEj`tPfNwFC~% zQX~xPw_;8-8<1gK?a#652XdIayXF?u5>%*G!=2-LDO3GQs;Nloy-S%+*k>}W?dn!Hr9_} zsUqR2yibxVdBI}Hri?&7^m~H=9!MN*DgAKN-8FrSgfFxh?Xvvwjty|h7ma%qbYyS3;3qP8`de#HbDqHi%n22!$9ga! zcTlB^yj^9d!*N3O2Y8^GUOH)nuN~ce6^#3ifsz&i_Rp1%eyw#$4sZ`9LWQH!pqWfc zUdXmf2Y!lp(L$HQ;sGobF`@${B0tKFNlX0)7|9_rl^v+I-`6o!D&tL57)D-?V6@5{ zqRDN4$^{g8mPh=_6ZU%dQQ1$AO)jl3_VCnA3XB=T zuLn>uHi<=%3;+8ZuyQe@g$h#zV@V9ay6DV+Zo#7uaUkjq z+!Y0ov*~cfqiCEHPN-CKg4yQnP})_oPxotJARbKG#SfI4fVE%$Y&ggg2iW8v$nqH4?rhv#7FtiM@ z>ZiiADPhPav>0leX0_T^_oj0d+&;{)BJ~9mRX*Lrqg42`NwXCYK}DZpFBvH-M&j@D zJHu7cLMU$N6)<0m4-Fs1qL49wy>-{e?U#B}8*+3+y&iJcDyD(RGkm1#afm(?&t|}! zO9#y<#7nqY8-hC~)Yo^=!jlwG9rFC2rz4*&a8UtJ645XV_FyTChpfM^P-OnSn7WEE z)t5x3=){b=8%gNOE3I$GQf&vJL5ivBoL}am|+-0n894h-3vYm)i=s#}KWETYb;k+~Q|ITCElyG(FAAn~6{IT(glw+cw zAGa<~ilC)&Ot`kYD9l^4lK=(rn|t@(rad#!x zdC2I1Qwi82h~{SD>$13D9Q{jpEEiCI%IB_x^yDPp>VY!L4`#=`flEx}xe8_~cT4EJ zR{x2m+qPc25)HUdkN{j^SE5^;v-y1EB>^H89jLjIt0*JCv7@(hBJ+32p!#t|WGN-^ zXq#5iUXz|kN!$9SV`wz!!#;Tx*Cus*mKpJ0rxMeV#giTc=9}tMSCtgWlQjigaQ$=L zYdSBB6VbRYuH1Ga1Q+Fp21Y|6VirD~RoldF0$0wY8THn5mPAi|l)Hlh*GwOE^v=y( z%s7?g5li6YOkJ{8S}aI}IcIGM`XY33WbvTLD($@0`q#q!h)t2FHwPb1Gz~|^a{_wk zlq6yYKQ#rt4UyQvBszQ$kkeu}XnlS;FS>9L8Xk-i$14bd+3`bv!Yp=BS)Wt@5E-H{|RUG`%8v;X_XBWxT@*P`S&^dEd6hoOnCzhBFu z@l)p0#!noCrY$9n@SASdSuk2QR!`qa6eYL@+h#j3lU+t!9RvE!S(Bg^W&9wLuOgOU zb9CaIq#IS1>*JWi!^#ZzjX1M&qNz%0=Pj?-q)Ka)TV%kZmY{4#UWA-^xM0#lcsRwz z9N#?^JIyo3*0vU;>a`henyc1qAd{out0pgxLj(0H7-V)^bo)c|`u(^}u0NKmzoNjL zw-P~!YiTahu_||-x&j0KSBnq@tYyqzOszzl?r9H}rE#MCu0wSs~5FN#SvR5LL0OIk5MhFw2d|&6Ul|y^)doE;84$ zx6OK|H1|rz{BW6IIhRI%di9|M?lBB6D3OES2lAS7nP=c|t~jN2s#QJGeRYvk?SyhA zknsQo&`y73_i96+)PJWz7<(ET_A$icEYT+i;L-~SJu$>k<{*F-xy<-K-yxLzuMiNb z4O|NNe+IvS1`F4$T3?0g#&~ zv09o%n!`VPayoevEm=OVnFuHgrwN@Cu8=n2=%YWf_-RviMS&^JN#mLJZJ>SwQVd%( z2fpFm3}qIhPi%B6b=qU{$9@qug3I4s%Xn0~{3DxdFQhlpt2OV5dM4Ws;Kx7$$Yrz# zR&HLew7lz>_sGlHZKb$)l2A6dK3cw<8d28$Awu1tRS-=hjBu3k4#gOP&C@Hh#ReYk zPUH!;JZ)>3boyKDF*jkdrS4@?KyU?eIOqo-?|jh}Xq%j|DCjR4)U^6xm4_YYPwFc> z;F$NyV#&T6GAh4f+JO}VD8x(!GG{JY8E`O(S!Gl{GRQ%GwLZI5V=nX0cbjzli=ad> z`sC!~VO*0sQJWQf;!dq=yPhD);%s!w(fg1JKHmMg$=&abqZ!jk9ztZ~2YoMhR{8w1)6+tz zS5`X&E2jhcNGr*&b~ApMq#l{2zHo;x<|+#xSkt zLcr@_XN+MZ-ipQ45U9N31eh>xkNp@nUibZz2k&S>Bs0`e$}@?R_MDGAR~1J$B3cbv z!8PdhSTPT|K=^v!vf=lLQ*{dv9^QEm1(W-^6gW>qP?=ge&e)+CgsPH;XO=GY1dtW4 zymFXKxTx-O1G-S0K?)rGriZpk(@N92@5Nd&mYJvtW?(pQ-ySj`USj`tpuo}rzEnb9 zGV#A_G=|oGYJZv^L7K0hHi)9wY5SRgtozFAn{gyS3Wj@P&Nm*Qf}1X%rSXV;PykRt z&A#V6rTP5zcIbNHsfOH;P6If579R5ZKl_?}9^Kml*8Tn83mPS=hG2d3AYilhOvMK( z+|l-Hx$b8pMy!!gB)Ip^>`jMtwN8neyoNC8#w|jQSOpH{!ymcspBy|5tYKO~9AFm3 z(k;GOGh~eRqeR5}02Rhopx6K2<>-T=FYX!=+>6_M7ErV0+dGv84`6J9qiEzo{i8Hk z!-X-|_w%-4nbQh4gvn6IMI^{)Ay7}T<2&X$#|*b)4Lt$+GYih9mN`cUM^{{mZ0AXp!2KvU^I1e6Ii$FTKxFk54R2dA35FRQ3wRAZCGLe)%D!? z%tXkTdlVY@p%9iI>zI-8j6Kzq(1O`ZfEd(0>l5JIm)JQsnn8f8UJ6AvDh>|xs+|f5 zA=y7&}ccVnLQhI8x+8OK@4@y z@<@Q_+AZezQv7A`7FLka_j1l9bivbe{D?XIBI-yR&6uzWeYlDx0(I1PLeX#nWQzU4 zah7*za;j+p3abY~pMcahpGZpvM%Y$BQ-t&aHKnW()Jnmjk*R73_iVKu_N z_|c;1CZM8*6^uCqYC-1z_v0~M{tGwv^Q67~jeLvmZ*ImLv@(`q^K_wENF!M`1qN)t zrEUwq&r@dl9o9i1{B1o$_Ymy2(gIx3d&tSkxK9EJV9iI2leEbP@=MP1AC0S${QDZ( z?7jlZj~)t#O5@Ok6kxOwPO>zPieWt;`QJ2_=r3~y#lQb=H-2z|wH0!nvDNQnFQUd_ zDTGE7*_pwjq<1Fxh@iJu+)$qXQvKbVdo=X#|Fg~7Q=)S8$BccM?9E;N&(!tzU^|2z z0C@M0Iejiq0KI6@_0?-?! z7$R1A7Iy?a1C3^#Xez^G+!yNAckwP)BisMLdw4%duXnkg`x4*~1z-hSWDf&h07sXA%p zQ>tE~cVR{WXACSHNo0_6CCb9m2@p+zU$gQ^xHO_5L<7!EwGwQ_#5C#f3<0SCG?2AM zQ>lu4f)`AGQ(;w%PWf-6lnTPWbRFR?EN0!2L!<{I9;~8a!g{RH#57V!O)EShk0n+? z7z$)t1+dDt^`+}S$kxW1I1E|i5kvk(|8Eb(3)wak=cU%bhs3V z!Tew(4(EhK%xDu%09GetV1IDVGv?Iy!AyoTu)byu9jt86=NuD*2iZ>}HZASpCXm{g z<-A~SfjKFw48#RU9S#|%C~EIZAg8xG`ow{xsUvXftx3*d@Ks?$v8LLl*;#;bRRNc5 zhf!zBy8rPM;e9#T9lHc)Lv>ubdUkESnBND}Ql&(D(x0WVGIK$w3r41}d#Hf2-Y&^E zqetwfLEm>ul{GbNhOw|-3GVd^WHF~710cq?Le8Fv65@NNZUWvLpsKl6>pe=_Y~-O#n4ysW!9Y&rN4+@m5%@okO} zU_N~A<@E8kzvX_q`=G-$V3pC_%{$oZ<9feP{HOwPF>k>=uog<6Sw@kErg-lTuAyy+W55d~b~gZ%K3#b(0|-PB2`KLtQje z4!H)&Y0rk~tfjP>x~NFntJi7QAGa~$=M1OA=lrO}p1p%V-IZckU(qZa%8tg`440)E zz@lJ(3H(F2nTIv0y-{GN)jG|Gb(#7}LZ;%(2~dL4@CGANp&8x)MZr6f;;C_=epz<4 z6B&Z9e;@qr?dQs<+!v2qa=WUQ$SvW2(&T%j0>^c?Woe7$mPCodF#c><-VE8yhZiS( z)wgS>mg|p_7TdT+`U^Z=?l8yKMs_pw!JI??Mj=G22F#;vGae0^U+DY#e;B+!k^>nn z0VQWVl*bMFu@+{zYHv79?fexyN|^o!-Vp!`<@G91uh| zh+=G7-&%yV1r>q$^Hv(dzGzgF4;>D5ec=YoE>hkHA($40xd>nN700vu)i^Hmf%Q8m zM$Dz=P4Xt?f6wVRe~#A?{*@*{bjt87O0skHV`7~=G}~&FPTyED)qmwN1sZ;foW*22 zxk=AIOT1*gosQlPB^ZO$@C~+hswQXTnLjBVfPZ?XbeNui3V6WxTbJo+xDArt-awWq zzQyqXc*|cS0)Agfm3u^BSya72I{{`rUqreY3$Soesw@B+*2KIEaWpyv9k?vDYcl$H zl`8}>0iq(Ju`F;TP)h38CZgOkf>-mSwo}I~!_e%iZ58dt?P^y|O?#tG8FeVMfC5tK zf1_vU%lfcE-%?SaVX~5f{8abZX!rg&fp#`}eg6|@#^xonHy^WkU6?=JZ=!f)ThZdTMTW zFoT!G=!5UtYWPmx2&Bqtq`VQdqep=`wda?29X`7b#QxScyb6*a-T^9K>*{v7!0T;8 zwy8umG`w#o*eWx;X+LO2|2-fny&=0B7$E~EskF?0t)}F&9ogNo!FN0k-tn5d46mPQ zx9^TOT0@qmpZ7e0Xg0%0thSS}Q4z(6-Oin1E8zNtR17i?w=U*fl5 zL-^feGue|U`ZRi*VxWuP0EQx(>z79>4opPpa7Z&-cp0AUHN?>=K^l&onZlvgN88jS z6G-Qfd`%u5WFIqOYv-QMReA8@U_52S{VD|2DksExmt)85P}$<1{mE>+l-FrsCNQig z?2q@(Z{%Os0~HA;|E^&W?lDYx$<|E0F5ix5ap~Guw;Ubpph(&@y3`J1h`bz{(Dwa_ zF$H1tTBNXTNbF!K*MrZ?C54|_8?b#{Textv25+8IbkwRIn;VW>psL(|HTy*NQ;K>} zLyCzEg$AxGcSSvX4Kb@twP4EkjYCtYuIDA2 z^O+GT1?`IqyH3&Oft@x8Z{VwG4?@X7JY5zd3z1pUgEE2gp%Oqh`7nd z1XT@?QC)m&_u%uC5_F;3*nFpo@>q zt?^s=X#38@n5z*BH~rV@0cg6Yxx1CORA;SiK6}!R6azWwl#E6Cl~YwHai%}l)RMs^_Q?z|0n7f3+s(=EuY5qcWqgPhs3)cOTTZsX1ui^XdnvqPle&Bv+ zc-v*{v$n)he)?C$j(npQHvip~$(>9Mz67h=3zL-VamY-jj@|DsEif3T?% z)x0ol6w%fkubEy7^rq|kMZ^Qk0e^n)T@<%HGT#hyk_js$0+^T8Q|~_{Qy%{6|DGK7+wOo!* zkcLpI-IuV5ZuUELmDUBp2c@PgJk10YQ1M<+W0u|fu1a;N`WpKF8rUZ|AO3p#K+xTX z%a8%!R7%~&MiTeFz(zbPu73GwQ&OWmr147C$|Os7F7)4Sz=dBSk>d4{FB;WsjgzL|S+H zcqlyq?m9wy3Dx5j1D@?(umel(<2jSYy%#STydDU4;bYIgxwC~dK32Wmd6`~DxC*ZT zIIRjA>=(ru4u-K|u#P5Mv!CXu{FmY#zeU3FccUndM25cd1Ap%8(ERx%Co@OuwI4q> z4RJ_>C#R9|hq>{~?bZgL<@_mpsWtsS$xYd|GHKWC(_Ky_$pX)vwd*PYsCitVx6N5l56muuH(90 z_?PFacN5aDO4==<5fHCz;L>{k$Uf1OHB}cqG!PF_9Uz!!)_oFupg)?L7kYIDl3IhL{%?!%cz9VY0k-A7DQS@z z9I$TN|JFacx34KcVwBfzt{=ZrlEW`QE%y)}%*)1_U(R}~jHn71s*)ZSaN~isu;X;y zz0TbI+bz9XX4rIO9YNy_U$M@D(b($p9%NJnSjSGmCNiB&`<(Psfq^GbU^gaWUG#G2 z&WBM3@mUdtZ4+7Otnk3QjaO}Cw$B^!h#K@b$*O(+K>}2` z-E??Mlia?Ry6Z^uPb>V&aQPi9|6Za%l8z2s>`1uH|FE7<@^-XvFNJh(P_Y_&FYAxu zX32tiQ+0N(jHKkfr>(^()~h#iXIexIN-Sd@2AU4YIxh}L76`YC%Xk624g;uy{~i+FJjMgY32%GA*-H7uyuQ+iea0BdqH?w`g3K(ZLbW&oh!f4>PaqJ4hB zY?QpSN~t=h*s<{dni^VTU1mX^Ji$VSF!fWN6(}mBMPg`@bALjDpAukx$Za9+K|#TU zY`0~&24kjXG`GKUp%aJqHUI#UbT51X9sX1usTqFEnwynSeTVlo06ezL7r32#yh$1~ z@6g=Lmoik3KcK@G(BVs&lq8j+8ChJt*oC^Uk4<AaE#233?WW~A@2VcKU~$mWeVx~OEZ6Bk8g!-$1k!yd z7#ID`(&eTDoM^s3prg3_$%M!M2zG{m@-!#}A&}um>NG#5Wd#tNpN)dTT%>0PENf_P z4CCh|>^gz84Bt=&n30O<*=f*|-Q9?`?Ete&lSIIw@BSE5COiUj7vy01>H_2! z%(g4V6848c0;{v*S8`=kqWNSPJ2oD`k-A3PQmmjf2E_B#{x5z&z-j z9Uu&bKr|}RdG&@OHA5&3f*y}?bsg>9Hq<1J12aMM9x$_u+#bG;^sKRK1C!Y+?9T)f ziGjk{0lTZ}4Q-snfh=I&)XWf2jZ#Hs4^pVawjyDoTaR#0_5iPLK8$$o#U-&oTC!=| z%4^EH}mq+VD3vFOW=wePa$Bcr2lNO6F2u7?nYxVL6()hO01)?(jZ+5_&5%e+bpi(d z6%0P4wAOei?f?WnD40==slUHr1s0^$5&)DJRs8_qd6xw#hIekMDJvELAer9;;LPFM zsX>IKdch#Sr|V8GnYWSwEO$+r0+{ISEj6W; zBfsy6yX&5NmQw)9&~dh)^e1b}-dp`C+?uuG8V z(eaH33^MQf(8mu;$Pge`02E}#tSR#O{C^-m$C3`R7u6MeO3%i!{~xm$mhWQ(H^2Y@ N002ovPDHLkV1i$o;Vb|E literal 0 HcmV?d00001 diff --git a/_site/assets/img/fortran_logo_grey.png b/_site/assets/img/fortran_logo_grey.png new file mode 100644 index 0000000000000000000000000000000000000000..8920ae6cd463082f01b3751ab9842aa53868d8e0 GIT binary patch literal 19657 zcmZs?19T=qw=Vp~wr!ge+s+$1nb@{%I}=T8+s?$cZJYDYch0%@{_3@=3;pb>da74f z_1?8BQb|D)0Tve)001CJONjyh#ZUjj4K(DxJMCvu#=i)}87L_NsF}t;`ODuCM;DoT{Pw8c#Q3B8I4Trf0{CS*gE_}0|0y;JpYomrY=Ur9=0}i z&O9Fcr2mEB`Ir7rF%v2Ae?eTV`AIe9m54>{olJ>27}*(_Nd;huiHZ4~Ow4$IViNx& z{x8Q*YT@GIz{AAk?(WX$&cd%J2`t;OuGVV&uVK=S=qBmHe-I z#7v!yoh%((EbZ-x|5LBgPkUDvep1r^H1xl(|LLc#!~br`&iQ{>{o}{vVdTKX!pO|@ z|0m>PY4(4*_y3Uk&y)Wa`!81i-5B4$q2UpAGBt9scT%;tw-NXcBTGALXJaD=)Bo_| zWBPw1{!dT&{!=B7qLZcRKd%2_B*4PQ^#3XQA3Pt^f9U?-=>PZF{#WV0!4-i0*V6xb zQ39~o6Ka|OfDk}hOjy+eR1nD1{6)oM2~w^;`pZ?Wbqk3n0>Ztpy682RPdA4$kZ0 z30RWQdyNxZ2CKbAyr~xY)8sMqW3!SA@j*D-%_oP^Y1r1BxJOg{WaEg+2g~BOl7+u@W&@u)QdotMlrUe$nacE8TjFOzRx7}hSVx2ywZ8oClUdroV zQu8i0m2pi7DF%|1u0z!%AGl6BpkbKG!{R2r)IQ!Q#Ej4zdUg2z!cASFL1j#wpyqQs z+6EnO#~r@n>5eY)sKTKLY}1<<>rN@5JK@zmuF{|=H`F8 z(l{_wX)#cNE6i*U_XFw|o5>87j^&^1XdC(HR63n;eAx}flF_ge~z%r$&L@+UoWROo(m&y!JP}D|Z!9n2LLFhXX zB~Z7(S!u=YhR1m5t?0Zqkysh+tI#VJx@X;#iAve=F#NVSW+yK4lf5NBwrbSi6fBUbCJFA(KlC)B7<_ zD1?#EZTB(Fnt#Q0h}&Y&IfP+4P|TMxNfETQbiV^ZPRmJe)CoV*yGw-A1f87t`6%^e zk9WK51?Ut=Z-T0i{iw!Y{SNmYnNanK{}X*}yz|ykZJdxvT|E75_o@PkHkh#1`>>~H zrSg2+FA$Ge^Mhs5?Z|m%z5qoz@YI-HzV?MDu8NmbS|2L62y-a@5_yryiKu7gvCrcY z+-Ju;ybo~~ntBhJ^^5WT6Z8E=QWynEG~BDnH1coPSz2e_DbO5lV6^y_WNRCQ@d6sG<@rG7L2JQ?+=3hEH9PH zl&|xO)q3P}{na|-8@%J1kDfOIW}yd%^F=dfO)Doq#w#dzGd(>$09_z*bU!gM+Fe*1 zxcsPcI_C$v>f>0hN!^hC=u3=Xg_0m|aw}(0i;7CJU2P1Hqvrq!#spGEDQ zkZGwIQL*CfX7DLr(Y-xJ3ldXK3mkWR>{Fu z=H3eoR5!wZgnr^m!S?5MnBWJS_5p*;wT_v&PDH%PUD#@77Jp*eWNKz>98n|ejhNaF z%+kB3stWGuF!F1-X>z1-IEZJKA#(x+yQ|o+pHagkDm7-O*6ug!v33{y#Ugvz4l(rYICuH#coK1yAo2olBY@MKX!W8{ z{3N`;1eN;sesE!TFWU|qTSO#}CYM~*NA=7c^y@V(W(K^C7oe(#NclevW(T-%Aek6a zj~>-}e)S2NGbd0({@Dzgyz-1wtNhUm2y$^;kq$`e_CKdKs&f~({fWs@*c^<+syTJL}%Ru+dg!+(`dX6a;s=JU& z%L6RnJI|w{XJ~nz^WsyZY7HtlpwXs2$iRMB9m#nG2WA@!-H&Oun=mY&|BV@bu>aV- z+}c_4;h?`1Wostf?e#w1Pd7ri>c-~HgAoOAXVFCu^& z{Xmo3v7BIIK5)#;Z>Sb(dEtkBE~PDyHyS^Zei*%dnzKl7p#c(q*ISPI9`mOVMXHRd)d5;B1wa&rzj2vuanIQ;UQNlRm0UX-wT6=fQS^Mb8x53n%?}+K`wLp1uCCDd4Qo zybky3=tI!yrIl7iMZb96yVkvFH*jQ8cd!~O)lm4v03&+aZBp17-j;q-*(S?7IM9Px ziP%4I#w}pyIH6cRjFJd3=}RaPu`d*vZO~^OYIJ-Ut|)aQO`=|SoY@f`5*~6nK9Dp` z^#}9Tlg#awJguiIv7esG*Rs`*G~XVSo=$;4ioC_A`VZOvFLhf6QzZ@Nd{&|*aM4!oWA@DJS@{z~}|-j{hd>2E$m-hAD!o20vn?pQOu zOl{dS>mA3rvsD_m(8PJ)Sz7@d_@ZEtbe{;d?9LtEqsPpzlC}=kW(*#BtUzCGZz!_j z1xpTGf z&@(`8OrglA#sl>tuaJ)j^pkk9gzs$3zZ0Pobw;%ARx>C0Y_Z`V&tG|QT6E}@BHo!! ze1yZG=b>;YAPIuWNdd|+qJBe*_tD?B-Vdcp)7@5K70z#`v?VPLb{LEH0Tu=l?xikn zQA2wBd$#Yw`67(&^+Fi^dzL}6YVF_IjLCm4#mXMf|Iqmhadq>K``_!k^`$&=_8h={ z9RJy~i-GICe#PW**Ki`ZvvIK-M|m43jFV1K#7^sV>oIS9@Q)9G;OFmo^oxCtr1+yJ zoS1#ODgYbrPw(8AC4(6-s)p>*S`7oW7>VWgxYLKhoQ$o~1~UdcdT zgTxe|DVGu(4}$kdqNw$C_$=A?!PLtBRmEo|SxEXg<4%MbU_06&3!9qZrKcCv1-UCL z3Escpw(!P8^qSmG#lCZ{Nk{IGDg=HT&8c<|Te^6b$_E9+?PgdhPWtV*ocPp(wCS`W z+5tMKJ4Zc8&SuGp1zDE_bbGJj0N?o1vsSe9KPz6C&NL@{v1@y)nQ`_9&(654T*5;S zlV)y~7uKQnDCH2p7*!fE2!mvEBV~1AZpJ)PV&9=pcN2x0Luu>+#q1|THpJk%UWcgI zn8)FXXVDVW#lY8JF4QORk`>hR{3^~uUo$k+1K*^$@9|Ztsg}X>$W>t=x=lMQ7+G)@ z*hHd%#9S7|uO~s}&mu?3V0a5O?Sgpm=jMJ}j#DU|TKo>#7lC(BC;)Nb3<|S$u9w@bH!X8;k2#BtYlz16pY)9i1!{s52G8 zq?4T7FT{tPz}a$C_0!xUlj9Y&lfrQ|`ym@B+NIhPUB#?pwq6k=_BxH1U;FS|e6MW# z_=Kry$0$C7C;kE>Pky~?hpar;yYGr@ZGr4HwZGiG!*setbbZlcC<1RYLQpegJ{Xn zdj#h?z=$iIQ%lJ*>tYztSZjI9KEBtMWtw+{v4tf=JmA=DvZ-jdL&#d^D-gdWmd_@?3@KELv&;l}X}N6YY=>;v(hZfNUGtW4ir1hT&Q!@%KQp-O%4 zr3qlH6%4U7l}|JT(hI#lcxD(WPahoU!i@YXTp>SU2~mk^fG`t!i{W zSx5>b`8(auNR70gZIi=WlC}g(zk=n~VUY~+OArz)*a+~MOnGBCNQzI@=Pa_jdV(x+ z-xyrIK>Paq(B_YODOU<@35p5I+z0WYQ=dD@`~)atRc`19xQUmH@zT=~?+h3|^DTS$ zed})g)6dsU81V0WEZ@@DB-exgHk`*j!yLf|TL@uN>_uei60=>F?3ckOrXuZ5Y}BgD z10EKCdU@f}+TMP7=1d0##(+%Y;g_yKx7>oL2aH zd%TaYPyy@c{-ZZH!{2{?vP702*#=DPa82?cX=^R=i=h+6(7eEsg=1`1-WAp+%B^(S znu~XAwAPa5H9NZDjv<9{5)3G`HJfL3TM&s6mP~R4%CH7WX?#%z*|dKzpzg$b8F_UK z>@}Kxoiph*73w+>0%m-OUZUma&oWN%orZ4v-Cu`C%M$!!Fq_^ zo{tv%-1A17z%VUNY6jbS;2gfY5cjpZ+ndA>T5I|HkxS>66NPgT&VaJGCy1ycwnsA? zIH%7AlKsPI^@`ngZ^ekdR;xxc2yTEvgDYCTvL|9|HTq!2*DVsxjy$k$>b$|duma-j zL`$XJ%x-LU<$Iq=0lYYrXas-9t%_zH)<-V?Ya}q9WtE3T%uz;ZQpWI$G(lY`8`P^3 zbbT$jC(O;A&*ZScJby1y;X!wZ3XGfCXtx6YW{>|bnwrA^)ES1H7ruC;RTVFTI98*g=-T|*eVFoVP(!$(NV`5l8d90%T%6N!Nk+zy{0?-fs z5Oymt;$33wH%Y(XhW?vHULocT7&zQqHO+fH>$|m4cl-_K;bBRoB~ju9DxurIFdus> z)(j^Lse-xQ|K`ee$9XDj1G`|O8c&$p(d#?HSXyuC@K zTRGqsb>HSmGE(Nt3#a{kYJCOzrgaZSrCf2s{!I?MUHCUl9wCE~AdG=QJXn|HEDB#p zJk*@6pb}9nzstjvv+EK}C1S>4rG6Y>1(G!on`UMzV1$Bn?%7zgAPUX3%3ek~w)~7u zccw82GelQJAo@Uv2sf`ASf`q-u*D^bMUoSTN*r^`aLML)P;hMQ!4~$R!gWS0C;@D2 zrCYD2s#)v4U;@?IR4U*6(mRH>>{oNQwVYFyp+p)7Av7VLghlrEQyNuVmk@E_d36** zrZ9p>PiJw3>Aqf>mO4R>9osyOLM#;Wo_E}o=Icu8#@K)qVE#3{{yJ!pHpchfIM3-&S3WTa!(y3;9B_5@-C}JDD^F5X#QL+Xf z(Ct&Kh;Ng5avWAOP8+}#Oxw$q$c zAQGjztqRnSg9vPPYQ3Jnvzq0vbQCk)gA5%8z0Xm4MC)vg7vUZ?=<{Ka2AihXN+4sV zmVteQ;7x!Jd>476yfG&Vm4m@E60B@!IezG#2+cRqEe})vH;7bYaE}IFEaG#Sf$!QXnfn7BuXJ=>o%0hk%pdJ zp3WG`5>t{CFN%DrQeGOg@B>&Y2y12p)3P}{jQh}b$$#^@M)c<+Frx)$*2V zR)4hW${fg#f0~$Vyx_OcQ%9>oTPho#7K_{ZdFw#-v5q5co@fc8g7N{|-~!71z6%mR zXBr;EOS8|;#p$e6){s3JoCNG%2G1RNyi_F*JUcVqfIZ?C-4*K*kc-_dGv9APoJOKoyJjnSmor`+OY6=pQ zy1R%XsAWjKl0qef9X**QjXD~Z*Mkdjm^66&(FFy2O-3QygcW>#4VSMKS_);pQOv@0 z3M#HHq6kg(Ata3UXSN=cao!DYXfLIN1s|AY>9QFRyl4~sa6<`b-|gkqafzR45eF8= z;FGC6rBd@)H;kgi+(Fv@wfP@QbmW_%O%6>~8)cRQ02((|PBRun>Qchkr|S{zpDpNK z-%s6~t2QoU2=7+;{IMSt})OJjQ zS~2^uP%W!u>Z2971q-(EL8ZscQm6aX;VTb62OruO9$ful?_JPUJa2P8bKrWq=v}pC z304Q^hIjRH_TgL5g;gVBg9;^bo8yn#JMSs8K18XxA*Y{6=ac#)aoE@^a(pr&^yD0S zsjw6p@{rdd2dPCxjOVR|suqRCM-d@81Tm&A9#Ui>%@3AG-!vB;|GwgG83s~oB_}O` ztf@gBi~-KC>&$2a%2IL_%?y!Ft9207{7^+@kM9t)rb`BLtt6;OF57^6U41TY6bG1G zhtS7m3;84Pp9jn3_M#!tYFWj=xgfSA19OvZhf@0i6hX6o(ckYQ#RaSRCvsd6SpIbj zh<(^;`dj&^2B;c6uJ`9NI6eLQ*jgQDVILepcrq8QdW|0i&XzEW_BLBcRj<8)@G1U~ zE4dELr9b+EMP?g|?OURI?W7N>U3GUQy>z7u0`~5k+POwTzOfUGFPzGiTh3D=4lFH22az5?^tEVAa76ttU;w$V!x zH$py)Ma3-Ng)W0rTx6*G1ndi2P%ha-zU`wXRL|Xf7rP~oWcT6W!RmA%904=mF5Z~S zHh!XqLb}NgFeF?!HdRC24uI^*icnu8F^||upwVe_f`%#%Yp|*#x{Oy1(uAmpe`HNA zV}nJ1bQZ(l8+G{WN?Ha+h&q<;P>WLZj&MVD;BaPYbSJIuPz7R^E3lEKtDHt7Wi(1R zgO+~YiW;lcFBWz@36o~(6$+X&;lKr0QC@wIF<|?=^E--nY|~UkC0$ubk7izT$|AuT zaocqc-0eQkqGR$#><{UuPaG>1W2HC@hBS(uYfn|Di>qaD#Uu+B;n7!#ugzPqw{f3rxahZCI{Z@DvRwS1)B}>ePnn2$+;dhA)D~A%+ zV8rxR14&I#komS80WTbbiVa3&%yG5Qy*XA4Te3IilIH@)e)J4z=_f8 zKjK-AX8cO}%zSBv#}2!gqan@ALXFqjj`Q!=gtX2)bk5QQGHUHUZbb-aDzMH<@y4cg z7*~6JjwCty*+&?g8fErNla6hmBiMxEkzsMb7S2WN^F$HMJ{3D?Lr3e_pTyQ4CR9*d zZLS(QgQ+6CF-qVcrX8jGU2Axfe@g9v*@Tt6{=Qduf<5tdanf5mjG*9nyiNNPUW3Oe zRMNhWTv!OEw$#b;vD@NP>7zme`C~;`p;C&RfKLwa+>a{9ND!yv644f42A(R?2vG|I z4P091DQ?ISs+Iuca_+cPJeumn}O&Nt*gkm$?(_O@(2e zSj>7qck7PB?dDEYJbnR8H4_EAF*S~s?7+g!{PI;=6^W7ofHeuS5Pqs-$#T@%hqt$| z;w&NXF^=yY>ud%NnlD-_G+J?;p2h0<4_`~yGMubbK4a?`1y7t7lOcB;k#)R)9Dj3E z=jmds$$8P%9z1BxRsI%h`XYY3&>QA5TW}wrQnm}`>uvxf zdvRThz2&PDhpwE2fYvZQ1&6EjCzRtK82>eAgpe0`Jn7X;S*zF&&}qX_-;x~W)wPj0 z3jhfsO3m09lq6Mw=|p{v6{!YIrmc0s8FlN7Hds_4Gc{f&e6$jkIMS{;MY-}XIT~_A z8_H}bYIWA9e*D)j^`tC$P97qJNKRPGa5!#e@B5U=LLL)^L=(%h9dbX$(jooZAiOd# z+_qL8&=INDM9=fYdmKiVQ;@75_(<9#bVmSevA=Y!ukgqmchs(>(v}I4V$gI{{JDlC zP=LF zqRTV%ty7gY?bktB;|*DxOU=2rLa2Bj!kVHbVOOM+udG#j7x7Uv4(V^8@&wrlT&uzFh}k*KJXKJ zobO1G7p(*`PJ5X2bh+j4w=Yr83$tP({EFg>b98AujaWmO02hdq*Ya4j@?!{Mc=0~{#+u>`nP(WDPcdrrU_Az*1c4f`v6o&+l zO1YJmh5J3#iV+nmH07k1l74~O z(Wg!m1YS>9w_?YAbM1~TgeiL<%9Vbr=Eq87DY6n%+F*|Ms=)esr}+zo|Ab^$O)z&+ z(=jJ|T~BZgnwzv$Q;;#CHcUTTLBI#;dl=|;x}oW>fbC8-d?bC4vDeR%n?_GyBNBB= z^T`oDzG)?_VrjhG?_pG05n4`|BYumPb!;#!7y;_AAuPDP{LX?HRahEo%n+?U?)zzA z_ZbuY@^)o>1%>FS<(0mc{VZuFLpAZtGA$-tx)IBi>ABQps<`twPFFW5?Nir2#ZREf zfrB>%lZIL9cBAaXkB*{E=--bOJ=;mypJh8O7>0ZovylQE)xtqdTOlzMBXOKu9;;4{ zQe9VfNQ4f@?9++%pYr`~{x|PBCx<1mML1chQr@|^YR&bVODD>|tX-&WeeNI~H)cZc zgarh6%y?zQwjjcX7R}g9Uqf#;+j$sp*Vur$upD-1*bF#nl zqs!AcGRGXwgTr@8&AldWw8!BAk7>9LKTsub@*Hgc+6ypy&kRn6I?s92sqN(cl9f18 zcaRMLnPRnUsZ4l{#l!4KQZ9sO3Xp&c9U|ofNeQJ!jj8`71Iz0Xh&G1wZa7+5%mjmhv#<+#&r<} ze)QS5^*r6I7Tm?+nF&&U#j>zzx1DuX0yC}Ec$^gXg;N1()7eZ(WqR74Vckha=l#gj z!sgE^+Q2%IhP4c;p694DI4o<~+L1A(4U#=d!!}1F{y{tK&d3uUAJF^0>H{Uq_}}&M z_ZrCiWf)CyJ%69$2`|*`S^rr(yS!g-_W&=_(#LAzH(S<`GNH6&o%CoDLx7B|?!upr z!Lx*` z$=gD~1KPr9uDh@&_ck@E8I(kwxghPHXSqw>EC*Z4OIqIC67RWu!KTBglG|&zE{sm` z{N)s5Tp7{UGO7BBR}vcs2K`Llr3jzX>!%!;bk?A5QsN?Bcl{5kub3jjHj>yPLToir zNp}8|*|KPIb~yrJiB_Fz+;uLL?hW?`Mge$}rULpN*h6wEc#Ms(hU|b86=tW-Jf6~5 zTu^$pVh-^64sw>H4me;(cT#0@hcENZ&%ppKWlkPinxer46^R)evJ;_hJUr{zC*D1Y z5n2uYb?LUE*kAlu>p&o$Sk2PN>30Z@N^NMda*wQcsB*8Q@Sc-4YqQwtJ)QFk0+`8# z-OW_zE3=``>}aqo?zkK_01UenTMi+hG_k;8Eu{Zmike&yPgKhvJ!$ChR_vqZoM_93 z009hN1+Rt>B78IV-?HAn56~P^HwZ2Txn&2Uvvu>JzPs!T`|6&({<@N(VaUXpo^$3X zDf#sq3`zkFh3dX?JuFw&Lv^MU-JK%A8+ z{jU;LiblP!xHIVuBmpiK^_D%Z9`nM)slvcG=(AtA(@@qr;&;5>ZZ}@gEIrq7j>s!u z`(+<$T)4VFvv_w8ytTP`VWhTvHY1_E&@9iWDWn9SYX?!tJ~6?AFU32C?yxW!Qw?o5g$ z8;^%J>pQS|E}xu;4$BYk{LTF3b9~r*W_o+)aIRTe1B0GG+;e`|w&}C^pXGX_<*RPa z3P;lS54#w$>e8m%zug~|V;Vf@jw^|3+VGvMx#%)yp<_l2IIO7~|l5l{p+lrReCuu+fDSnW&`{@q6MTYha1|ym-C7J!e-?Cqn6z|NVL9 z84;!N0#8l8)P5}v!bpJH@M4L#E?#Q8_DAf2iskAElh&M>&anD|Jv!_)xLdB@rH21m z0YNrV>C9a-OUpO5w1)W?a*igAhyWr*^WOP(wdAG{DP&+?cM;<6A&-2iI0cG;ddC3$ zZe7}3JzAc>bYrZ6yD7A(CJYT@I;f=uFjZe^qgDCwlaOhf=@sSlb&j7N3ZRgnO1-91 z5R~Y^kW@Zu%&xrfyGtt11R+u@F3D%gm=KVAHX1dY03b9)AwX-f>+Uesd z5k)<-0q#l2la5VES&ILypq)fyrP(A_2#%*5WbP_20QpINC zAu)vY6*|*6|9mlrp;hB_AZ8%?xzg*;H?J_5U|CNq_N#@=+NHnMQUE1k$TG^w6IJtM z==91*8{7$tYHDx^J=y959A+ijXtJ74jAKWx|6Jc7YDD8#P;;wT{HNA)Zc&)$EOi7l zQXGHGz!>C+(E*n4LVo=krdpjWQg<(&n%7JlMo@uaFq^&$n$Xi0pvXH%iv`Ch_B?^DLa4p-V+@yw zi~#M@BnqAEW?9NsK#~P;x#u5^$p5&_A3RPSq`oOCCjFW1uDyBi2Ll4(HUh(RQ#3~n za3Or-9>SiMgLTrT{l^te!V$m5R5&k*+K0-XkUy+aalX6`31|B=nbCCiv;ODOL`>;# zQfFNRP@cS7{U}EcA`d~Q1Zx8p2IFiB_)wWO=u3OYLT;b37*3Z0YCJgUu}pOhYZycd zS2>@iYuLa&@brGTi5l- zrSYWl)S{MZhN%K~)Jptt2)>l(BI!cEcnQfpz9)-Jo2W&FIQ5i%1#yIElBc+^13fN< zy`RMl2~g%J5s3`DlOe*2mgQ6r?%mk=xo8zTBlIkQdr$*;OG`^`p`@V#K#~%$v{#cX z+vUE!0seUKBwl;W_hXSuTgF>7valeTfQ+2uJ0^EwWE#Y|G3~_kM!qT5)Puodr_`V9 zC@^c;X*yw8LlUHb6isDa^y*K8exWLM7;QK+f_g=+!Yl z3}3~%@{?L~?~J6+)ldC32AByy?}SfjnR@<%`OJD?3XrCY1+z&{7oz{~zsT04d315D z1s^kJoTj=hjJ(gi1;dK$6}%_Wx>r;>r(^giq#uv#SGNIT)ef#{05wt4dc$c2c349W zS@O)`-k|1})uR2@$e`XF)p+xcndoTNYceV?RJ0;{zLK{y$y{HEDZ)b8iup9(G|y3i ze&I4j^kb5QmV*uuEcGf~ODN?pYklazMC=s^=Z!A1U>aH4s*CrF`nqU`(J!abdNz0! zq-egJI3M^2B=;@q87eY5C7u%m&rs0ZLKasY`Kjd^@ZjK0P~7ls2bT}f%&d}_V0_M3NkP!A4?tYT(85)_187AAGSp>m!&Nb3i9l}2e?y6 zPk4-iPN*qoyce9w#sRBUw+egIr5Z;bq!(F7MVaA%;EcxpMXn6KIF>nN%AV?09w<{O(4IDEdj&A_{{bqOI!B|^3;%wS*Y!`oY#xt(el zv4E(Sr%g7R>skfjo5glwKERf}{>gwHp7vu;d0xv9qI&Zdb+IZ&ylEcA;b-{073^ay zY{C`&9=w3mw=&!LN($clFA;pz9LUn9^OE4pwe_qa(3#AHhc`$1$V;vD0HV4A`VczN z{*mU!K()9Fx$0rBwcuYRpObiqtC(+*Bd%eWSK@=g5M_x(efLn2CU{k){KqGfzy;Zi ztom8VMwh!V!qAH*7?HQ~QiTKH+(Ej6A{H%go_;T<^Dba?F7^&sy_CR8xz%CQHGkOw z^;~1y6*a6$=EO0wkXtx|AI)+@(irrlV~za&&weyWK_-*(f@b~kTHg=?QtHZnEU{X% zRJO)zyCOi*=LArV$31lDv%Oc%kKwUcVwLOWBzYaMuQ7nF&bdio!EbKTh`bC?g5&)Olbo}5D0~HBdkncKt&yFJNnzf z9)jdrNNsx{(u$~p40~O(Kiq~ezwWsI-8Q2G2~^ZO*ucf%R9GRXZllhGv^+4Z1)BjQ zx))&f3E_#Y2p!wilp2X_ncw0@YE~zLdSK`c_dT?xf*ppa%(*y>DNE?JTFmT-ej<9* zs*EOl-jqd^UU$z(1VY7p2$|*uw)scsT+5B-_s%UYLe$P3;4Taq)>G(Ar>j8hjuZx&lom=R^?oy+#ST zAo_G5#8c-P6dVX9^%xG+!bzjb4O><@iC@J)%xlgktJzukG_YeOcOpw$m zYjehYzW9~4{fh~UK++?_LLtIm5N+HFZ3Cj4tQYTyAyC`i1A;O7I3K%>SH}0N>c3DZ zX-Zhc!30L)9u52JgF#_h6qIcTWZ?4~!L;jAo~e6>96JuiQNuj-;Xey41`oo@!~3^K zWDBKK@9hicoUpQk%2b-GLcxw_+^)73~b zIPp;P@MyHClhbA5dUx4D!{xdyz+G1;)13Wxe^I@;`h8~{7Syn)c)&avu-=9XuuIOo zDDvPd)$c< z+?&RBr1r7&@>zl%3LZi&`M%z(^i8GVPE*Tk{Fp%GeuRT`2i^Z0GSYAfV5K5go zrq`TEkojK5hF4Mo>c&b?psO!dH3wR_W3+FmQYu z{k3(!p+bCCuV{BPE!r?~d-gkXH2Hg()4Fv26d#u=>%u;}Enjkwc`-5~^ry;c>jx(J z*b}-oQ1Gmkd~5t9Ha4uLnau7F`L{>As&)m(bvW9&Ud))MQJk@7USmMLt9Z)_u>T8! z`59{s2LzZkRr-R=dxQDdvFu9N>1PpVYD0}z|0Sd_9aKo9g6(1*x4C4e3hlBps!xBgo)D$ zIsz#r*kk@O+=~!B<~@G258k?84~6uik7j;3Et$0hnH0%u1wB**vt|rJtCt$?D z$|K=wFe>{g;I4Bkj{N#Im8K|?Hkr%cRY^>2bLy>xAfzxXQWJc@UpRgum38Wj9j=FY z1*J;^dH>D%=fMEwYR10ps3x9;LSXIVS^ZcT6~CFvApO0*EbtnW=!8tJhY<~Nj-w8iOCS^j2OzjuF4jP` zAsE(V4H&mP=(5E>i3I=T_;<*tNDK5pAX@E4a#!b@CL;5uPjYB5_ey}8;g1nSYHDYe z_t|D8zmmbPhqKgiCxZX-!S7Ld7Z`<|hPJ5(lj|lpYyHXpfjLAp>a@Umt3Kch!j+^i z97u)rv4FpeT88>)4AmJVPnAl6JYgB(&ghx__fGDeg@hNrNe27JGVWAw=iPGWwj6JC zIN`PtQaq$LdTi<_F%&qXiF4yzb|b-w8~)y{2MIJHZ|JiUa$Oli2 zk8=_+HBtZNt4v1EwJXPgcY-XTZ#F&zSAAPkr;Rbr24-lE*kRjoq1xGrX0zh_h3gN@ zJotR&&xL-F3oH3hn##7H4DPEaySP0&04%q85+1IYx*5?eq@Xe03ialyhh1rLBLCtS zE4JzFZj3Y7Qno+}_XrmI(bgMF?dlzER`mRshDUwMKn&*X_3bF@8A z@;j;F$^A~_#w^YYN)1#&$UI?##N>CAlauI_R8+hrw&WxY>Jcc#%$`It4$^&P*1W2P zNLQ_RXJHHarz^Y7fcEZQwdR+llrrQ4s1PDt)T4TmGyn32fmA!>01v`gj+XRH$+Mc zBRJ?wph!lbhK|R|!D{EMthH%6)WN8B-;zYUM&e4?Uto*^I1zBie6j^zp(hOSxV5in z*QecY8Qr(prPvG&-B_B(#*Ce6fBTHkp*8diEjX{yzlysS*ch%I7Q>DfON;WY-9x-# zl@#ZIDxju#NzgHCpP@8|x2eFIMRL(3jtz6U|FBw`LM@rn=Ts*Oo8I`dL1_{JBJ3AR z`N8}`jf{BTX!77dN2DJatknC)AXwc@k2Kj~)*^=(bYfi47jcH)1m3J!K0-*&oc+`% z&Mlok9K&Qp_yKIomlJrR13;JMH5dA!QU_zVZ9c>GO;CxJI1@Xv$QF+2JT;KswO;K%cm;unR= z$x%uS{07@YL3fbR`6M2Q2$pxEN5v7?c%o#eggs4!t36%YLU_Qs+ihlq-!Hh4V?GYI zjL;+=sMF0uVnbOd{)~c?83<3C_2v9Tc#&5&SP-?T2^0(~+97#EU+sTqR=WAIqz0X^ z?bumJMB(MaO*aCk_&1p6O`s0F*6s-3?EnBDFK}i z;$hBy22{9vI21bP(RQr&j}jnhL$vDtCAxSzW{bO;^+nd( zA^7I3_QjhliUSE$%gfI5tDwNmQ!TFi-54gO-Sq^fcB_;k2w|X+*C+8hagM;%F`$4< zKvhWxEj=FcFra6u)nDH~ewENTe;q35ax&y~ekR(D^mQ7zaEekInzo9nrLdVe3OT4q zSa~ow7YTM#pZ6NPA@EL~9u{QI3$72PQi&_2OxOpvYG9amZ0aEymPRVLfxA9GJa5iW z8PR;+-VlQ1ZTEC|2wiHSo~}c7erfntyQi+fb)Di*OK?N>F?)mz zy#c0=!AP|%J;eb5pRatVF1z!>o%)1D54>@V$Ly_07Z+*i%qI(~-p{NR(#~6X+>22% zIgUvvHT8Hhdr7&p_K!^+2)>^i~kg>%dUrq(T+qbOG@}zu5ShHyy2SNyY9s7=x0%nMNrfdoR>G@ z&!J^G4qZRMuO2SyHN@Ls|0_IHKaQ3LXnO0^#91Tlx9eWPEj>)MgJ zW+x?Sa`_;h97JsUuL+q@dIO};)Hh*3=O)xHLp^}fRCY1p;l`=<9NZ1vTUv(>)|-FLm7<%TCG;) z*!uTA@ORJt=*!P@&`G?pMYCHrDtHt$b8j%P*)ZVaP*WGfpWnS<_U@0rRti^kbw)K$1_K5I$zXsM?*dL@J-FqFEss`S z=^lG!v3;4E<4GQFPD>k%uD?zL3jWiwnln9eWwp$+!N7*VfHX>y?=T2@S7mOlp=@0h zzV8`&s^2=r{r7)2;Hs6|{_os3FL>FDw!vujYG~m!nyr~u=V7h}0|o;_U;yVh;%H(I zHtG-JG}aGmxCHQuEn*vs#y=)|r!`S>XO#@A^2lAG{WT zJXJ0i^%#4g!Mx7PTnz>`IR?lt%@T}aDi<&NTP&kQ57369CL-+54uZTy1*aGjqumc>9|eYM+C#f(7p>J_>`qTyD;ft=v&6Z_*kJ zq<{fV_4?FVJ;(Jt&#|!U@iDx7FSbzL&hp93d#hE+A927FJ9AawjX@s{f8~|aTgpxG z4w&cPSt=CHAxAfwa=5Kkb4u{oVTc1UCJ%#w5imef4?x&tXb)O8rl@QS%RL{3So@>K z($cLr|M`8-GXE&Qj8I-j(xe#52C(pQs5Wt5b=8|ng{6tN!57clu@~eGFsM;2x9BDb z0JOl?Hrx!sHID=*DVRDcZXOH#?TPqClfKYN!t{2g%^deOT2n%v*inOavxO7Cjbv8LFIEvx7J&i&hGof@3& zHmsd+rF%XMZ7+sgej!l(9B}U`RN2`>GQia@-2Q^$;pkG{%O+|wJR65W)sugfa=-kJ zulNq%BFKo`GO7tV#(-{PDNZR>Be1G_zFU5)@7TutQR+$`%J5VRkH}zPiU@?ru<(0$ z{0=DPL0rFz488_O%m4nJL(aG6=s+YAI99f*cmW?`X-MTr(e2y35U+A3zmrF$_C$vL z?#rjoXt~yNT}PY)C*RM5h&~7H@*E)h`%$A)@!JMwFH$W+JGJ$6#ph&R&G?AP&VWC8 zE8AJ#;*o)D-i;8{*UrD)afr9Fvq0SL5jr#J7OkDWdj{R#uF7_#7ZNei95kj@FprM1 zD!%@}YxJW`AAJ#xsP21xRrTgy)j?}K@Jjwv_?GQ2Ur0L8jLPo}vh9Ij4)egg4cs2Z zClcU1K7R|1{}|k+f75sEM?A;+&kuZP?nx$N+Gvo%33j6cI1UO7uC>Q#l+^DvLQ*fd zUxC1!eJM|j0F%$ppKBjJd^lLyBSzC#rl*U?ceJ)SEo%oF;WRkoKLaD3Ga$N8$GpPn zVDVEhAUXw=JsFL6653`9Mo8mm{W9_?qQTJ@=#D@W0!!$J9(D@LP{`ZJ3-zqOtB8^4 ztH`4r12?Phbw0SFjE;OFpOUy$JkW^;`4s+Hbsq&Hl5F`lyu)Sr9TJfVBWb&p8~Kb| zg@2-4GbrpcFi_!C1k4^GLJgTN;_GqTA4BFx(B_Bnd_4IH?0uDrZG|fP zuqqCh;gw1YW94Iw@zz){Zu!oH9rzRQ!8QQ{#{`tGahT}Fp^1%yY{o$+W6;gYAUSjZ zqJ*h8o?KDHa}nJ#H?b5j5byvWXv4xe7WCl;~RJ79eXEF&xo9KAEN?>RY6MM2%Q}`4Gat^9M)}B{Jg#R|6i3wgk@NTthvbuSyzS;p&Fb&_K%?DqyK2u*`Us&%kMk4 zPSvfdd#mpIoOAE5hUvO>?|FRZ_nqJU&htCJ^US9|wfvFhM}!c|r=ME;41Iq{|M%}b zM1NQAy!1!(b?CD{^{F+{=YN0t^*?`^?i~J=r=Gna#E(44|D6}V^28VD<~^T3{q&Rf z{OjVg#dU0Vb+zB=xcwycOeZ9< z3tO^~PP^T1tPaR4MC-tH-Ge9@Ha1Q!E&t~)+=_aR`#>NL0?Q}1mt5Do6BU-~U_%Ix z{tMA1vhVEdaGf;HNEktCemkxYNIU@R?j*1b=*{c*P2Haihu=V;2n2rb&GU^gOHIaS zfsGH>+ifB_5lTDBwUJsjb6jfX&}Z`P2m%*TEsDzn#s%q3&G|!$efqzkd7?~1j+3;&u0(( zW-V7yq;}}dw5TjIh@4eTh+h>16v5eYzq++`hX|Paz*_F4<~NbD%ylI5zrX(eb80O> zRVpINQ7i(A=t1t}m1AxM_ZNz^7V1pyyp)1;>VZIz*m;he=R#^4-Cj^5+jX?m^{9d< zWl;zyatC>oB`-PElqCV~CxFmd5JcR%BcKc+^N9JB6^~4ong!s2F(p)1VGth()Exn~ z+KN|cu}Dp7)xig$(?XAUKp-3epV%kKU|t)p@dytYem7O~o8KfnAO=E*gNnOAAPWM_ zD<*W>rg&mYt(pcPbQZNCE)bZHK-#8wB2t6U^A&**#USw7Up+{!27JE&#pGaqs%c0b zo8ahAn_mGSVKot8V!N%@qU%NP0S}fuR{xsUcB=&@!N|A<0zjY?1RN%`zsF*Jez8d1 zCD%fn6#CTj0YwNPkT(LvyTOhx-y6%k^yiYAo87!Y9E6?+C7uI;;t*i|aci0RI4_r( zeQI9Y&0ZZip_|v&Q_Y{v69CVF01$|efb3t(?r`*e?U|N(bJKT21VYCL9U*~0(Fm|3 zl395~l3ERpq1inPK0E^g z$S3Q*79cj}2nYnqKtK+l&6w^AB{(d08LB}ZKp-0ez1~+t``KY5;e4hu?{ zX3G|_fdCLF0)a=!FFEhaR7+vjg38O^Q=m+Ogx|G9z@hpfPhx%h$hR8b^M2((6dDpIrCg%lmuQ9`%^ z0zg0~0;9QUNos18bC;s8V<=B249FV@Q~?3MbL}2*=bFnS|Evsr8C9WxC<73vEdqmn zwIuc1M~=wv+Jb?C1A!_a(DDl*$=qz-&@v`p1sqWZAYcjtYT*f!nkKs9IU6=bc$P!C zKQ&1v$YKftzxiu#{$ah>0u0u+I=mW1&cS2A%#_LrIen^Uhg486YqNfh65DOqb38ve-wh1KyX}Z@1eE;#RR)<(>M+g*Zgc)}qf0^86fw zEfM7og`dzUp{jW5+mB$+Up@zQL9|8!_j)%a@j~|ndP1yFt1Rd{B8Ug4A~zCK3KQ&A z_^9tuhV!q6Ns*@kvAOBbw5Y+^HpSl^jOnoKEVpu7(;@v( z+fvqqZc!qOMK#7*Z?^-3g)Lr7YeUP0^;Y=`Pr9Hr6`ouy#bn>6R;8&#=Y#2Z?T2nI zF*n#!7xVe%5B$XEN>~e!6~yHe+e@qrSy{**>&Oj~C-_8g(K4FolH6G_D5e7Bm+HVt z7r$(WFI+A-w=n(L8>4lU9}p>0DvsbOgefZupAvZC?0RT+E;~x|h}`~Ln764KWgW@i z(;^?h6e@g$ZbrSdF7KRo{Fku*0_Lt(l*hmd!I7vawIuZ{gj8j6$$t!ouTU9z^E56%c$cc`z|^%Ha$;Od6>{lY*XY79S}1` zxRT{y9r1r6G<(4J2Y*YJ!Nly0sjMb~BP)z-hBL8+8CZEHBBfU*^#bN*xEvGFD~|Tu z&8Vo_VTcxh```XkH#$&>PlD5RC1z`UR{jf^x=LiVc|62;feRE6q>cgZpu!l{438mp z?SkCAexLM(%`+QyCN@Z&pz24RF`6KW%t0p?k7Q1;f(iI9;rbFAq)t$&n>X}$a~~6N z@z3u2VhL*j#`3iMha$OLMQM3i5{mCME}VVk-Gq^98+e5<4c&&7eV9!)krL(YupED(FaAZd~kD)1^P(f;w zLc(ad1=spU$*mOSB~-^|I7nSy{mLUJ<}@sI3MA_^*a%W5tRSmO!j$5;qM2_QDeS z`TQ@v_UGwoX=dkauLif1lnQ}4UB_hsw)G;yFnM=kD!(_+cs+sQ2IhoyC`5 z{#vPJ>b&FK)w@@xI1Pf-39$_xg^@67rGqn})B5qH^_-;+T5*fOanAFx7lyf!&8Lc( z(x?9GwOc2II3`Z7ojR9K$&iXR1TyWWXz3E$KQcsD?nUKm3c-siAJQ!e0eN^=NqHfg z*$9Btv+=>xm(S$CbxhRDPa&8q)v$1E*yl1Bj$zQw&8Bo_FRM1Hq<%`WUPzxZ3|Q(Kx!Mb zWPyyCc5GQtKAS`Yscq7hfwC%ZC^)v$9OZ!2Np;am8ln2(*$Dy7XIVQ?CcMNtI{eSC zJy`x)fW%@7G{sY3hA2}A*zJU%YGVVi+EW!2HxeV@C5~ZKgsP1VfYe4+FH41KWm{LR zn^XgDF4nD%i>fUkbrdqVKNkTWFyo^q2WzS4hBq|;d2_LMY#;3t zTsZs6yIh8>8$5JwC7sj(NIi)Ne$PdKy>o7CoLs6#U(|VgZh>P2&^_1}6w%^SJRbha z-#%@{T7V$lmAdwu;PNDlR7dg{3r4rQNL`C$o>II~X?ne{@<@8J_@n5#URg}=Tya2R zF%VEoMPmfDE{MCcb4z4tPkTZrXAIg4f9BGai(s~PHP|6Q-?{S`OFEd-vc7X2MBNxh z28GIS4N_+Suk5HKjS7rD+3m&G&#mJfI8qzEu2(4KGDYA#9P61jSq9`)+ z5C_dY1Ojh(8TeDv+JoP50W>S2ot&2>n-f>?;p^0QIBm0Va5 zykx+U9S|rQ0g$?AgpocFC>a5ex@5qST_^&Ta?l-G!V+(S)FpzAtbjln2!PaOpo~0# zK#2%|)FpzAtbjln2!PaOpo~0#K#2%o$5x48=b06|AL@41*2?gd*`o=c>9f1KCzo3H zddHn+^G2WJ4ZN#hfGQk1tMAr^)DM0A{{PXm7NGD7!bfXxCiAvg%1xNVotWNGE_R(n zA3o}G+?j&E)pHmQ7xp1g8-m-XnoxemOjZ8v3Yb{pA^VB4gw%`9F!17BEZDv`Em9|t{{2y$zT0aRo4QjGTQt-RFuty zfb2j32#gQ_sYh7gDh2|+<#y?8E;Pwwz@;b1nM+qLg4ueow?5awx>bMmX@=5ZsY?d% zBBFxS5y0SfGy-h0`6-#~h3HUtq6-0#S{L#a$d|W*RiGG^D*{MulS(~vgni+emmcMX z>A|6KbEK=cBp`LY^`E-*PJi(#N9GOPsS`oOLJ$C{3xTyhiOQ4ivlJH%_(}AB=4+pL zIJdO`AowJ_bAGSTiSKiQ)avmH`q;+l8>BW)C3Xq4PJL{W7|n5m)CN);q>Oo@nAS=d zO>?<kM82We2Gff@-R@OjrzKf^Tm6gKT+Ndt(ZvSrCv~vjQrSy_cmFu8a(8p9RD5xFGd7 z9)n-^9{%I^gg7Qnubny<8UQyV5XfVM{=fg}GoOq|9=8)B0D>n348f-nK=))C6P9}mEG3RVZ zO#rD4QH0H64365gxd@e#9i*<5I#C!PAOuK_T95|UtaceFBM%@@A_5?FiC`luAW#MZAaxli*B}p!nwg_ykUF6* z@>m|3FiWF@)PnTY>)iK!b zzxDhRs31u+-)bfI5RfGO7-9GK_qEFqLretGhd^KU&9GT^wg$KlOD38ZmT9-t0XZDf z8wfsIb+voSbrqI6rrI~%mJxkfez6RkhG~Dn#Dp$&u!n!^=l-qiwE(GwH8dg!9$PW` zo8co-O_F6K6|T%c0HmIy2X5N1m87X9W177z%f`mZB}{Y8QC>|SgVZw=uSnBzy}=&q z8G%cFw6%5Z4ri%kEIE5*XD|XF^&I8!9I*+5Wg%ixKih@=LV&6JEmVq-8o-nJvf15g zEh?u8A;GlY;%2x@GQwJGSA|gmz?blZIut>+$wII1?8qkWL=dBXx}JB3iR})Skz%US zDD`L&Mq26*4!u)*axlbZ$~)C4DO#Am5U?4m&>JvWnIqoJZfZ#(VH0pzp!`3ViVkdvF*Qzr~#u zD*G;xe5`1m5G&+iMd?1chr83Et)CQnJc5ur$7UFVvE=bX4+6d3ac5Cha#FBOpN)-; zrDn4^*8i0ikqa?V8D+&BSa4Z^y+BF5;E%xl>Rj>^n7_92&uuzLkgwJVFrUeJg5Nxg?5i3CQE-IUAh93{5YUc*;xF@==d9Hh zKkb4+03ZMa(jzcfw;)L^c*HDyQl-aaStI*>rAvbhfq)?hC@;8dsl}Q_u5)NW%%&Gm zl)CrV`oAs2F>!kB)VZiIxDN!7 zlQit8Uy!mq1bD!VILrg!a&@I7HD%xD9YE!Yft-K<5Xct+PjOj@GncMh9Q|tLn-5Z} z9s=#^6{$KU@7HdAsTP_aza z4CK;*z+|VIWf+p0e@t!d;hUy?TBZq9BYA+mp~?<)s!75zQVUC(;D#bweX%@~i}*KR z{>v|8Ex;s)$A-YUIqr{@pXYO6jGW9~v2e?o!L%6bFH42fpUq8I-dFR9YLoi6yGMDq zjkPXh4Aw&`(YP7T>qd#QV|$dxNbRRA&3a<@BB`WG5$Sy)4v~MN+bN0YhX71dKw!9|3RCxlz+j_a+9-l-zdAUn^N80fV9$l(t|f`rCIt2OU;kM-vayuA0Pk(G$RmLO*Sb>q^0J7u-21s;WrS_ zivU|`cD1{;wG}x7G{aI0!QSt=2t3jjt0+JH_Ukl!3cmocz(OD(kOhJMdmMYxkM?AW zGYQVa=6oW$O@~oU77)LIKvfX9{MPeN_$_I7=9-e3O>qSVuVCRL95CIb5WzPPC>McQ z(^->}%(T=huv(?W39Ebf1_D5!90W$Zi#L!Ri`2Bvl-7s0;`Oo1DJOCP0<}Uw9$Y@~ zWi+qgu}IB{@G2G_fg8Ow<|U2iKmZ72MS%Inyo;Kj4og3Ab6O3pqkkO+C+-1({18xt zo;8&fmRn*{b0RzEa_7boD=j(j{f#6aPbTXBt>9E=;)PX^U_S!6b~knz7BzQcoy~PWB?JO^a9fKCJcxI`~;z1jfkh%H5Ho3nR8FPALRenen$eXIBlbsb{d}3JHAMia?OWT!yH+UUd0N zC$%b&wB(-G5G{WbiMr36LN5FS0ulkT!aQpBuM|IM>gq zFl9q%3aQ7+O{h5QbgBfCyw^MK?C=MpWD~?>pUv6`n7%vmKllLC}(I33{C*S_uXZil=CqKRR#!o(X>Hh(c C60NWR literal 0 HcmV?d00001 diff --git a/_site/assets/img/icons/icon-menu.svg b/_site/assets/img/icons/icon-menu.svg new file mode 100644 index 000000000..222352e88 --- /dev/null +++ b/_site/assets/img/icons/icon-menu.svg @@ -0,0 +1,13 @@ + + + + + + + + + + + + diff --git a/_site/assets/js/page_nav.js b/_site/assets/js/page_nav.js new file mode 100644 index 000000000..0f6d4e201 --- /dev/null +++ b/_site/assets/js/page_nav.js @@ -0,0 +1,35 @@ +// If the current page contains an element with id="page-nav" +// then this script will populate it with
  • elements +// containing links to all the

    elements on the current page +if (!!document.getElementById("page-nav")){ + + var headings = document.querySelectorAll("h2[id]"); + + for (var i = 0; i < headings.length; i++) { + document.getElementById("page-nav").innerHTML += + ''; + } + + $(document).ready(function() { + $(window).scroll(function() { + + var found = false; + var scrollPos = $(window).scrollTop(); + for (var i = 0; i < headings.length; i++) { + + if (scrollPos >= headings[i].offsetTop){ + found = true; + $("#nav-"+headings[i].id).addClass('current'); + } else { + $("#nav-"+headings[i].id).removeClass('current'); + } + + } + + }); + }); + +} \ No newline at end of file diff --git a/_site/compilers/index.html b/_site/compilers/index.html new file mode 100644 index 000000000..629c2ab8f --- /dev/null +++ b/_site/compilers/index.html @@ -0,0 +1,411 @@ + + + + + + + + Fortran Compilers - Fortran Programming Language + + + + + + + + + + + + + + + + +
    +
    + + +
    +

    News

    + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + +
    Fortran newsletter: June 2020   01 Jun 2020
    Fortran newsletter: May 2020   01 May 2020
    Open Source Directions Fortran webinar   18 Apr 2020
    Announcing FortranCon 2020   06 Apr 2020
    J3 February 2020 Meeting   28 Feb 2020
    +

    More…

    + +
    + + + + + + + +
    + +
    +
    + + + + + + + + + + + + + diff --git a/_site/favicon.ico b/_site/favicon.ico new file mode 100644 index 0000000000000000000000000000000000000000..a3603903a25b295d0a3e5019494454005dfbe159 GIT binary patch literal 16958 zcmeI3?Nb{?7{IU75B=yjKU!aB`e$_fY?DaUQ7ctD&ghIEl)I$$4Tw&yj#C{Sn}k$_ zA~>}5r7a>YP$^@fU`wG$c?mC;m)2nru@o92g*@()<7n^P+ug))bJ=t=o6YXt?d|V* z_VzW8qHG|aty>lHeZR8hQAN2|QIsvjlO!cbJf>&jqQ1aG5uc`od|G4JrwxU@>dmlM z19$sW9b>6FdsH>Nz39Po*`wR`+!yv}QNp?6ZdM^(B*Q-cQPib~9Ks&;Il{as0k^fC z#v>kW2TKNoxkN&4lN=&GwU{OY@}3vU&VHNE|LmPI2ziPgCV4Wpd6VvM^K0?XxA`A1 zWI)mn-;rl`k5uU)uU3uxtGZ9x@&6b+2u`{7$~q@yoWwC9E4?3gYwKae(1L>QY~ z!+*$8{gbw)HW2m^7JqGN)T!nVZRNF2wtsw9j5nt}{&v_g{?;##JI%kq(mm!??s^Y; zYJY*ghISY}+YRHL{V+8+1~+GKWF(j5$_o5_Z5pPBCt&i@5d7ZW3xmxUptrsaj=uh} z)BKq~&*z86{Z)WGqHZcS4i$x^nLpEoYp-jUM@8}B)Q5+pV#oJm^jwcHe@?Y;!L}AV z(<#hf^Xf;^>3`to^TPb!yz)U_^H;sJS3dsJ;`*8;{}s;%x%@cKn46k0 z`HAir_deb{X1((J)8PMVM=_U!HlEH-OmXj9FFszm{f!;M`v2nTx40ZPrf2_Co-F(a zpL&DIUskZ2I-it4~`zoOO*cq6g zxlRXPP37_9zEaos&462vmRMk`ObAmse{SOvD${^GAPw!8yQt;zknC5u; z$1_Blb434X?EmrfUtU;3!{Dxe@LZARa*ZF~0a_ox)IV8MCKlo}{M3I}vfbZV%foR- z)baF>W#iep)v@@iU*2cEd@b&T{s+=H{}AEtt!stEeB9(wCRVu{@uvONYrNJUxyWyD ziH5B6S4a5MIR6yUzbH3ehvx}Par-?4C-_&cXk(o!^)Wr$of~*)}~`My@&m{sm&^Gs+rsq~<3!T@kN#I$!y98!>+%U-^lx zms<8%;1R;_3j2p__cNULKV|=bHXvvp$7%zT=G7oOy45z2kd%|Qc3iaDg%UfMo%zBa z@u<6W&6~eNK7TL|WKd$JHpj@A@C=bbTtYb{LO%5cGc7%Kpg`M9_`fFJc3j9I`K0Wh zv5%wE+NY-aMUOwQI!7Aj*$TNsCaL-SFxDAu`_R78o={PedS+=t4>w=e!+XZ`a8rvO jZVc+-1|!s?cfZ{t0YfiF*rHc# + + + + + + + Home - Fortran Programming Language + + + + + + + + + + + + + + + + +
    +

    High-performance parallel programming language

    +

    Get started

    +
    + +
    +
    +
    +

    Features

    + +

    High performance

    + Fortran has been designed from the ground-up for computationally + intensive applications in science and engineering. + Mature and battle-tested compilers and libraries allow you to write + code that runs close to the metal, fast. + +

    Statically and strongly typed

    + Fortran is statically and strongly typed, which allows the + compiler to catch many programming errors early on for you. + This also allows the compiler to generate efficient binary code. + +

    Easy to learn and use

    + Fortran is a relatively small language that is surprisingly easy + to learn and use. + Expressing most mathematical and arithmetic operations over large + arrays is as simple as you'd write them as equations on a whiteboard. + +

    Versatile

    + Fortran allows you to write code in a style that best fits your problem: + Imperative, procedural, array-oriented, object-oriented, or functional. + +

    Natively parallel

    + Fortran is a natively parallel programming language + with intuitive array-like syntax to communicate data between CPUs. + You can run almost the same code on a single CPU, + on a shared-memory multicore system, or on a distributed-memory + HPC or cloud-based system. + Coarrays, teams, events, and collective subroutines + allow you to express different parallel programming patterns + that best fit your problem at hand. + +
    + +
    + +
    +

    News

    + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + +
    Fortran newsletter: June 2020   01 Jun 2020
    Fortran newsletter: May 2020   01 May 2020
    Open Source Directions Fortran webinar   18 Apr 2020
    Announcing FortranCon 2020   06 Apr 2020
    J3 February 2020 Meeting   28 Feb 2020
    + + +

    More…

    +
    + + + + +
    +
    +
    +
    + +
    +
    +
    +

    FAQ

    + +
    +

    What is the status of Fortran?

    + Fortran is still in active development. + The latest revision of the language is Fortran 2018, + and the next one, with the working title Fortran 202x, + is planned for release in the next few years. + Further, open source projects like the + Standard Library + and the + Fortran Package Manager + are in active development. + +

    What is Fortran used for?

    + Fortran is mostly used in domains that adopted computation + early--science and engineering. + These include numerical weather and ocean prediction, + computational fluid dynamics, applied math, statistics, and finance. + Fortran is the dominant language of High Performance Computing, + and is used to + benchmark the fastest supercomputers in the world. + +

    Should I use Fortran for my new project?

    + If you're writing a program or a library to perform fast arithmetic + computation over large numeric arrays, Fortran is the optimal tool + for the job. + +
    +
    + +
    +

    Join us!

    + +

    Mailing list

    + +

    Subscribe to our mailing list +to discuss anything Fortran related, announce Fortran projects, discuss development +of core fortran-lang.org projects (stdlib, fpm), and get +the latest news.

    + + +

    Discourse

    +

    + Join the discussion about all things Fortran on the + fortran-lang discourse. +

    + + +

    Twitter

    + + + + + + + +

    RSS feed

    +

    RSS clients can follow the RSS feed.

    + + +

    Open source

    +

    + Contribute code, report bugs and request features at + GitHub. +

    + +
    + +
    +
    + +
    +
    +

    Make Fortran better

    + +
    +

    Write proposals

    +

    + Have an idea about how to improve the language? + You can write new proposals or contribute to existing proposals + to the Fortran Standard Committee + on GitHub. +

    +
    + +
    +

    Develop tools

    +

    + You can also help make Fortran better by contributing to its + suite of tools, such as + Standard Library, + Package Manager, or + this website. +

    +
    + +
    +
    + + +
    +
    + +
    +

    Write Fortran software

    +

    + Or just write Fortran software for your research, business, or schoolwork. + You can learn how to get started here. +

    +
    + +
    +
    + + + + + + + + + + + + + diff --git a/_site/learn/best_practices.html b/_site/learn/best_practices.html new file mode 100644 index 000000000..aef773879 --- /dev/null +++ b/_site/learn/best_practices.html @@ -0,0 +1,244 @@ + + + + + + + + Fortran best practices - Fortran Programming Language + + + + + + + + + + + + + + + + +
    +
    + + +
    +

    News

    + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + +
    Fortran newsletter: June 2020   01 Jun 2020
    Fortran newsletter: May 2020   01 May 2020
    Open Source Directions Fortran webinar   18 Apr 2020
    Announcing FortranCon 2020   06 Apr 2020
    J3 February 2020 Meeting   28 Feb 2020
    +

    More…

    + +
    + + + + + + + +
    + +
    +
    + + + + + + + + + + + + + diff --git a/_site/learn/index.html b/_site/learn/index.html new file mode 100644 index 000000000..cbac9e304 --- /dev/null +++ b/_site/learn/index.html @@ -0,0 +1,331 @@ + + + + + + + + Learn Fortran - Fortran Programming Language + + + + + + + + + + + + + + + + +
    +

    Learn Fortran

    +

    Learning resources for beginners and experts alike

    +
    + +
    +
    +

    Getting Started

    + +
    +

    + New to Fortran

    +

    + Try the quickstart Fortran tutorial, to + get an overview of the language syntax and capabilities. +

    + + + Quickstart tutorial + + +
    + +
    +

    + Looking for help

    +

    + Ask a question in the Fortran-lang discourse - a forum + for friendly discussion of all things Fortran. + +

    + + + Fortran-lang Discourse + + +
    + +
    +
    +
    + +
    +
    + +

    Mini-book Tutorials

    + + + +

    + + + + Getting started

    + +
    + + + +
    +

    + + + Quickstart Fortran Tutorial +

    +

    An introduction to the Fortran syntax and its capabilities

    +
    + +
    + + + +
    +
    +
    + +
    +
    + +

    Other Resources

    + +

    On the web

    + + +

    In print

    + + +
    +
    + + + + + + + + + + + + + + diff --git a/_site/learn/quickstart.html b/_site/learn/quickstart.html new file mode 100644 index 000000000..3fe1fda34 --- /dev/null +++ b/_site/learn/quickstart.html @@ -0,0 +1,469 @@ + + + + + + + + Quickstart tutorial - Fortran Programming Language + + + + + + + + + + + + + + + + +
    +
    + + + + + + + +
    +
    + + + + + + + + + + + + + diff --git a/_site/learn/quickstart/arrays_strings.html b/_site/learn/quickstart/arrays_strings.html new file mode 100644 index 000000000..99f319bda --- /dev/null +++ b/_site/learn/quickstart/arrays_strings.html @@ -0,0 +1,631 @@ + + + + + + + + Arrays and strings - Fortran Programming Language + + + + + + + + + + + + + + + + +
    +
    + + + + + + + +
    +
    + + + + + + + + + + + + + diff --git a/_site/learn/quickstart/derived_types.html b/_site/learn/quickstart/derived_types.html new file mode 100644 index 000000000..3c488a7ab --- /dev/null +++ b/_site/learn/quickstart/derived_types.html @@ -0,0 +1,804 @@ + + + + + + + + Derived types - Fortran Programming Language + + + + + + + + + + + + + + + + +
    +
    + + + + + + + +
    +
    + + + + + + + + + + + + + diff --git a/_site/learn/quickstart/hello_world.html b/_site/learn/quickstart/hello_world.html new file mode 100644 index 000000000..d19d58080 --- /dev/null +++ b/_site/learn/quickstart/hello_world.html @@ -0,0 +1,543 @@ + + + + + + + + Hello World - Fortran Programming Language + + + + + + + + + + + + + + + + +
    +
    + + + + + + + +
    +
    + + + + + + + + + + + + + diff --git a/_site/learn/quickstart/operators_control_flow.html b/_site/learn/quickstart/operators_control_flow.html new file mode 100644 index 000000000..92eff5c4e --- /dev/null +++ b/_site/learn/quickstart/operators_control_flow.html @@ -0,0 +1,670 @@ + + + + + + + + Operators and Control Flow - Fortran Programming Language + + + + + + + + + + + + + + + + +
    +
    + + + + + + + +
    +
    + + + + + + + + + + + + + diff --git a/_site/learn/quickstart/organising_code.html b/_site/learn/quickstart/organising_code.html new file mode 100644 index 000000000..f8f7ea0b7 --- /dev/null +++ b/_site/learn/quickstart/organising_code.html @@ -0,0 +1,671 @@ + + + + + + + + Organising code structure - Fortran Programming Language + + + + + + + + + + + + + + + + +
    +
    + + + + + + + +
    +
    + + + + + + + + + + + + + diff --git a/_site/learn/quickstart/variables.html b/_site/learn/quickstart/variables.html new file mode 100644 index 000000000..75ed6a64b --- /dev/null +++ b/_site/learn/quickstart/variables.html @@ -0,0 +1,708 @@ + + + + + + + + Variables - Fortran Programming Language + + + + + + + + + + + + + + + + +
    +
    + + + + + + + +
    +
    + + + + + + + + + + + + + diff --git a/_site/news.xml b/_site/news.xml new file mode 100644 index 000000000..d3e79d233 --- /dev/null +++ b/_site/news.xml @@ -0,0 +1,465 @@ + + + + Fortran Newsletter + + + 2020-06-05T19:41:32+03:00 + /news + + + + + + + Fortran newsletter: June 2020 + + 2020-06-01T00:00:00+03:00 + /news/newsletter/2020/06/01/Fortran-Newsletter-June-2020 + <p>Welcome to the June 2020 edition of the monthly Fortran newsletter. +The newsletter comes out on the first calendar day of every month +and details Fortran news from the previous month.</p> + +<ul> + <li><a href="#fortran-lang.org">fortran-lang.org</a></li> + <li><a href="#fortran-discourse">Fortran Discourse</a></li> + <li><a href="#fortran-standard-library">Standard Library</a></li> + <li><a href="#package-manager">Package Manager</a></li> + <li><a href="#events">Events</a></li> + <li><a href="#contributors">Contributors</a></li> +</ul> + +<h2 id="fortran-langorg">fortran-lang.org</h2> + +<p>The Fortran website has been up since mid-April, and we’ve already got great +feedback from the community. +In the past month we’ve updated the <a href="/compilers">Compilers</a> page which is now +comprehensive and includes all major open source and commercial compilers. +The <a href="/learn">Learn</a> page has also seen significant updates—it’s been +reorganized for easier navigation and currently features a quickstart tutorial, +Fortran books, and other online resources.</p> + +<p>If you haven’t yet, please explore the website and <a href="https://github.com/fortran-lang/fortran-lang.org/issues">let us know</a> +if you have any suggestions for improvement. +Specifically, we’ll be focusing on the <a href="/learn">Learn</a> page and its mini-books +in the coming months. +Please help us make them better!</p> + +<p>Here are some specific items that we worked on:</p> + +<ul> + <li><a href="https://github.com/fortran-lang/fortran-lang.org/pull/90">#90</a> +WIP: Mini-book on building programs</li> + <li><a href="https://github.com/fortran-lang/fortran-lang.org/pull/83">#83</a> +Improving the structure and navigation of the <a href="/learn">Learn</a> pages</li> + <li><a href="https://github.com/fortran-lang/fortran-lang.org/pull/46">#46</a> +Build website previews from pull requests</li> +</ul> + +<h2 id="fortran-discourse">Fortran Discourse</h2> + +<p>On May 4 we launched the <a href="https://fortran-lang.discourse.group">Fortran Discourse</a>, an online discussion board +for anything and everything Fortran related. +You can use it discuss the Fortran language, ask for help, announce events and/or personal projects, or just lurk +around. +There are already quite a few interesting discussions going on. +Join us!</p> + +<h2 id="fortran-standard-library">Fortran Standard Library</h2> + +<p>Recently we launched a <a href="https://stdlib.fortran-lang.org">website</a> for the API documentation of the Fortran Standard Library. +The <a href="https://stdlib.fortran-lang.org">website</a> is automaticaly generated by <a href="https://github.com/Fortran-FOSS-Programmers/ford#readme">FORD</a>. +<a href="https://stdlib.fortran-lang.org/page/contributing/CodeOfConduct.html">Code of Conduct</a>, <a href="https://stdlib.fortran-lang.org/page/License.html">licence</a>, and <a href="https://stdlib.fortran-lang.org/page/contributing/Workflow.html">workflow</a> for contributing to the Fortran Standard Library can also be found on the <a href="https://stdlib.fortran-lang.org/">website</a>.</p> + +<p>Here’s what’s new in the Fortran Standard Library:</p> + +<ul> + <li><a href="https://github.com/fortran-lang/stdlib/pull/191">#191</a> +WIP: Function for computing Pearson correlations among elements of +an array in the <code class="highlighter-rouge">stdlib_experimental_stats</code> module</li> + <li><a href="https://github.com/fortran-lang/stdlib/pull/189">#189</a> +WIP: Procedures for sparse matrices operations. Ongoing discussion on the API can be found +<a href="https://github.com/fortran-lang/stdlib/wiki/Stdlib-Sparse-matrix-API">here</a>.</li> + <li><a href="https://github.com/fortran-lang/stdlib/pull/183">#183</a> +Automatic API-doc generation and deployment of this <a href="https://stdlib.fortran-lang.org">stdlib website</a></li> + <li><a href="https://github.com/fortran-lang/stdlib/pull/170">#170</a> +Addition of the new functions <code class="highlighter-rouge">diag</code>, <code class="highlighter-rouge">eye</code>, and <code class="highlighter-rouge">trace</code> functions to make working with +matrices easier. +Read the full specifications <a href="https://stdlib.fortran-lang.org/page/specs/stdlib_experimental_linalg.html">here</a>.</li> +</ul> + +<h2 id="package-manager">Package Manager</h2> + +<p>In this past month support for dependencies between packages has been added +to the <a href="https://github.com/fortran-lang/fpm">Fortran Package Manager (fpm)</a>. +You can specify either a path to another folder on your machine with an fpm package, +or a git repository (and optionally a specific branch, tag or commit) that +contains the package. fpm will then take care of fetching the dependency for you +(if necessary) and any packages it depends on, and compiling and linking it into +your project. Check out an example <a href="https://gitlab.com/everythingfunctional/hello_fpm">hello world package</a> +that uses this functionality.</p> + +<p>fpm is still in very early development, and we need as much help as we can get. +Here’s how you can help today:</p> + +<ul> + <li>Try to use it. Does it work? No? Let us know! Read the <a href="https://github.com/fortran-lang/fpm/blob/master/PACKAGING.md">fpm packaging guide</a> to learn how to build your package with fpm.</li> + <li>Browse the <a href="https://github.com/fortran-lang/fpm/issues">open issues</a> and see if you can help implement any fixes or features.</li> + <li>Adapt your Fortran package for fpm.</li> + <li>Improve the documentation.</li> +</ul> + +<p>The short term goal of fpm is to make development and installation of Fortran packages with dependencies easier. +Its long term goal is to build a rich and decentralized ecosystem of Fortran packages and create a healthy +environment in which new open source Fortran projects are created and published with ease.</p> + +<p>Specific items that are new this month:</p> + +<ul> + <li><a href="https://github.com/fortran-lang/fpm/pull/82">#82</a> +You can now add remote git repositories as Fortran dependencies to your project.</li> + <li><a href="https://github.com/fortran-lang/fpm/pull/73">#73</a> +Improved output messages for the user</li> +</ul> + +<h2 id="events">Events</h2> + +<ul> + <li>We hosted the very first Fortran Monthly call on May 14. +The turnout was astonishing–over 23 people joined. +You can read the notes from the call <a href="https://fortran-lang.discourse.group/t/fortran-monthly-call-may-2020">here</a>. +We’ll have another one this month. +Subscribe to the <a href="https://groups.io/g/fortran-lang">mailing list</a> and/or +join the <a href="https://fortran-lang.discourse.group">Discourse</a> to stay tuned.</li> + <li><a href="https://tcevents.chem.uzh.ch/event/12">FortranCon 2020</a> will take place on July 2-4 in Zurich, Switzerland. +Virtual participation is enabled for both attendees and speakers. +Registration is free and due by June 1, 2020. +There are quite a few submissions from the fortran-lang community: +A talk on <a href="https://github.com/fortran-lang/talks/tree/master/FortranCon2020-stdlib">stdlib</a> by Jeremie Vandenplas, +one about the <a href="https://github.com/fortran-lang/talks/tree/master/FortranCon2020-fpm">Fortran Package Manager (fpm)</a> by Brad Richardson, +a talk on <a href="https://gitlab.com/lfortran/talks/fortrancon-2020-talk">LFortran compiler</a> by Ondřej Čertík, +as well as one about <a href="https://github.com/fortran-lang/talks/tree/master/FortranCon2020-community">building the Fortran community</a> +by Milan Curcic.</li> + <li>J3/WG5 joint meeting, originally slated for October 12-16 in Las Vegas, Nevada, has been <a href="https://mailman.j3-fortran.org/pipermail/j3/2020-May/012034.html">cancelled</a>. +However, the work on proposals for the Fortran Standard doesn’t stop. +You can submit a proposal for the Standards committee <a href="https://github.com/j3-fortran/fortran_proposals">here</a>. +For reference, you can read the <a href="/newsletter/2020/02/28/J3-february-meeting">notes from the February meeting</a>.</li> +</ul> + +<h2 id="contributors">Contributors</h2> + +<p>We thank everybody who contributed to fortran-lang in the past month by +commenting in any of the four repositories +<a href="https://github.com/fortran-lang/stdlib">fortran-lang/stdlib</a>, +<a href="https://github.com/fortran-lang/fpm">fortran-lang/fpm</a>, +<a href="https://github.com/fortran-lang/fortran-lang.org">fortran-lang/fortran-lang.org</a>, +<a href="https://github.com/j3-fortran/fortran_proposals">j3-fortran/fortran_proposals</a>:</p> + +<p>Ondřej Čertík (<a href="https://github.com/certik">@certik</a>), Milan Curcic (<a href="https://github.com/milancurcic">@milancurcic</a>), Laurence Kedward (<a href="https://github.com/LKedward">@LKedward</a>), Jeremie Vandenplas (<a href="https://github.com/jvdp1">@jvdp1</a>), Brad Richardson (<a href="https://github.com/everythingfunctional">@everythingfunctional</a>), Izaak “Zaak” Beekman (<a href="https://github.com/zbeekman">@zbeekman</a>), Martin Diehl (<a href="https://github.com/MarDiehl">@MarDiehl</a>), <a href="https://github.com/arjenmarkus">@arjenmarkus</a>, Van Snyder (<a href="https://github.com/vansnyder">@vansnyder</a>), <a href="https://github.com/FortranFan">@FortranFan</a>, <a href="https://github.com/epagone">@epagone</a>, Ivan (<a href="https://github.com/ivan-pi">@ivan-pi</a>), Neil Carlson (<a href="https://github.com/nncarlson">@nncarlson</a>), Ashwin Vishnu (<a href="https://github.com/ashwinvis">@ashwinvis</a>), Williams A. Lima (<a href="https://github.com/ghwilliams">@ghwilliams</a>), Peter Klausler (<a href="https://github.com/klausler">@klausler</a>), Chris MacMackin (<a href="https://github.com/cmacmackin">@cmacmackin</a>), Pedro Costa (<a href="https://github.com/p-costa">@p-costa</a>), <a href="https://github.com/mobius-eng">@mobius-eng</a>, Salvatore Filippone (<a href="https://github.com/sfilippone">@sfilippone</a>), <a href="https://github.com/ShamanTcler">@ShamanTcler</a>, Amit Kumar (<a href="https://github.com/aktech">@aktech</a>), Bálint Aradi (<a href="https://github.com/aradi">@aradi</a>), Melissa Weber Mendonça (<a href="https://github.com/melissawm">@melissawm</a>), Jacob Williams (<a href="https://github.com/jacobwilliams">@jacobwilliams</a>), Rohit Goswami (<a href="https://github.com/HaoZeke">@HaoZeke</a>), Amir Shahmoradi (<a href="https://github.com/shahmoradi">@shahmoradi</a>), Bill Long (<a href="https://github.com/longb">@longb</a>).</p> + + + + + Fortran newsletter: May 2020 + + 2020-05-01T00:00:00+03:00 + /news/newsletter/2020/05/01/Fortran-Newsletter-May-2020 + <div class="language-fortran highlighter-rouge"><div class="highlight"><pre class="highlight"><code><span class="k">print</span><span class="w"> </span><span class="o">*</span><span class="p">,</span><span class="w"> </span><span class="s1">'Hello, World!'</span><span class="w"> +</span></code></pre></div></div> + +<p>Welcome to the first monthly Fortran newsletter. +It will come out on the first calendar day of every month, +detailing Fortran news from the previous month.</p> + +<ul> + <li><a href="#this-website">This website</a></li> + <li><a href="#standard-library">Standard Library</a></li> + <li><a href="#package-manager">Package Manager</a></li> + <li><a href="#wg5-convenor-candidates">WG5 Convenor candidates</a></li> + <li><a href="#events">Events</a></li> + <li><a href="#whos-hiring">Who’s hiring?</a></li> +</ul> + +<h2 id="this-website">This website</h2> + +<p>If you came to this newsletter from elsewhere, welcome to the new Fortran website. +We built this site mid-April and hope for it to be <em>the</em> home of Fortran on the internet, +which traditionally there hasn’t been any to date. +Look around and <a href="https://github.com/fortran-lang/fortran-lang.github.io/issues">let us know</a> +if you have any suggestions for improvement. +Specifically, <a href="/learn">Learn</a> and <a href="/packages">Packages</a> are the pages that +we’ll be focusing on in the coming months. +Please help us make them better!</p> + +<h2 id="standard-library">Standard Library</h2> + +<p>Here’s what’s new in Fortran Standard Library:</p> + +<ul> + <li> + <p><a href="https://github.com/fortran-lang/stdlib/pull/172">#172</a> +New function <code class="highlighter-rouge">cov</code> in the <code class="highlighter-rouge">stdlib_experimental_stats</code> module to compute covariance of array elements. +Read the full specification <a href="https://github.com/fortran-lang/stdlib/blob/master/src/stdlib_experimental_stats.md#cov---covariance-of-array-elements">here</a>.</p> + </li> + <li> + <p><a href="https://github.com/fortran-lang/stdlib/pull/168">#168</a> +Specify recommended order of attributes for dummy arguments in the +<a href="https://github.com/fortran-lang/stdlib/blob/master/STYLE_GUIDE.md">Stdlib style guide</a>.</p> + </li> + <li> + <p><a href="https://github.com/fortran-lang/stdlib/pull/173">#173</a> +Minor bug fix.</p> + </li> + <li> + <p><a href="https://github.com/fortran-lang/stdlib/pull/170">#170</a> +WIP: Addition of <code class="highlighter-rouge">diag</code>, <code class="highlighter-rouge">eye</code>, and <code class="highlighter-rouge">trace</code> functions to make working with +matrices easier.</p> + </li> +</ul> + +<h2 id="package-manager">Package Manager</h2> + +<p>In the past month we’ve seen the first working implementation of the <a href="https://github.com/fortran-lang/fpm">Fortran Package Manager (FPM)</a>. +Specifically:</p> + +<ul> + <li>FPM supports three commands: + <ul> + <li><code class="highlighter-rouge">fpm build</code>–compiles and links your application and/or library.</li> + <li><code class="highlighter-rouge">fpm test</code>–runs tests if your package has any test programs.</li> + <li><code class="highlighter-rouge">fpm run</code>–runs the application if your package has an executable program.</li> + </ul> + </li> + <li>FPM can build an executable program, a library, or a combination of both.</li> + <li>Currently only gfortran is supported as the compiler backend. FPM will suport other compilers soon.</li> +</ul> + +<p>Read the <a href="https://github.com/fortran-lang/fpm/blob/master/PACKAGING.md">FPM packaging guide</a> +to learn how to build your package with FPM.</p> + +<p>FPM is still in very early development, and we need as much help as we can get. +Here’s how you can help today:</p> + +<ul> + <li>Try to use it. Does it work? No? Let us know!</li> + <li>Browse the <a href="https://github.com/fortran-lang/fpm/issues">open issues</a> and see if you can help implement any fixes or features.</li> + <li>Adapt your Fortran package for FPM.</li> + <li>Improve the documentation.</li> +</ul> + +<p>The short term goal of FPM is to make development and installation of Fortran packages with dependencies easier. +Its long term goal is to build a rich and decentralized ecosystem of Fortran packages and create a healthy +environment in which new open source Fortran projects are created and published with ease.</p> + +<h2 id="wg5-convenor-candidates">WG5 Convenor candidates</h2> + +<p>Last month was also the deadline for the <a href="https://wg5-fortran.org/">WG5</a> +convenor candidates to apply for the next 3-year term (2021-2024). +There are two candidates:</p> + +<ul> + <li> + <p><a href="https://stevelionel.com">Steve Lionel</a>, who is also the current WG5 convenor, +announced running for another term. +Read Steve’s <a href="https://stevelionel.com/drfortran/2020/04/25/doctor-fortran-in-forward">post</a> +about how he has guided the standardization process over the past three years and his direction for the future.</p> + </li> + <li> + <p><a href="https://ondrejcertik.com">Ondřej Čertík</a> has also announced announced to run +for the WG5 convenor. +Read Ondřej’s <a href="https://ondrejcertik.com/blog/2020/04/running-for-wg5-convenor-announcement/">announcement</a> +and <a href="https://github.com/certik/wg5_platform_2020">platform</a> +that detail current issues with Fortran language development and how to +overcome them going forward.</p> + </li> +</ul> + +<h2 id="events">Events</h2> + +<ul> + <li><a href="https://openteams.com">OpenTeams</a> and <a href="https://quansight.com">QuanSight</a> hosted Ondřej Čertík and Milan Curcic +in the Episode 40 of the Open Source Directions Webinar. +They talked about the current state and future of Fortran, as well as about building the Fortran community and developer tools. +Read more about it and watch the video <a href="/newsletter/2020/04/18/Fortran-Webinar/">here</a>.</li> + <li><a href="https://tcevents.chem.uzh.ch/event/12">FortranCon 2020</a> will take place on July 2-4 in Zurich, Switzerland. +Virtual participation is enabled for both attendees and speakers. +Registration is free and due by June 1, 2020.</li> + <li>J3/WG5 joint meeting will take place on October 12-16 in Las Vegas, Nevada. +You can submit a proposal for the Standards committee <a href="https://github.com/j3-fortran/fortran_proposals">here</a>. +For reference, you can read the <a href="/newsletter/2020/02/28/J3-february-meeting">notes from the February meeting</a>.</li> +</ul> + +<h2 id="whos-hiring">Who’s hiring?</h2> + +<ul> + <li><a href="https://g.co/kgs/aogdeh">Intel Corporation (Santa Clara, CA): Software Engineer, Fortran</a></li> + <li><a href="https://g.co/kgs/5X3d2Y">Intel Corporation (Hillsboro, OR): Software Engineer, Fortran</a></li> + <li><a href="https://g.co/kgs/yuaohU">Pozent (York, PA): Fortran Technical Lead</a></li> + <li><a href="https://g.co/kgs/VAWjWk">American Cybersystems, Inc. (Binghamton, NY): Software Engineer (Fortran, C/C++, Ada, C#, Java, Radar)</a></li> + <li><a href="https://g.co/kgs/eLsn63">BravoTech (Dallas, TX): C++ / Fortran Developer</a></li> + <li><a href="https://g.co/kgs/eYftiA">Siemens (Milford, OH): CAE Software Engineer (Fortran or C++) Design and Topology Optimization</a></li> +</ul> + + + + + Open Source Directions Fortran webinar + + 2020-04-18T00:00:00+03:00 + /news/newsletter/2020/04/18/Fortran-Webinar + <p>Ondřej Čertík (<a href="https://twitter.com/ondrejcertik">@ondrejcertik</a>) and +Milan Curcic (<a href="https://twitter.com/realmilancurcic">@realmilancurcic</a>) spoke +yesterday about the future of Fortran in Episode 40 of the Open Source +Directions Webinar. +We discussed the current state of the language, how it’s currently developed, +and what we can do today to build the Fortran community, ecosystem of packages, +and developer tools.</p> + +<p>Watch the episode now:</p> + +<iframe width="560" height="315" src="https://www.youtube.com/embed/2NiS2tdDO_4" frameborder="0" allow="accelerometer; autoplay; encrypted-media; gyroscope; picture-in-picture" allowfullscreen=""></iframe> + +<p>Special thanks to our hosts Melissa Mendonça +(<a href="https://twitter.com/melissawm">@melissawm</a>) and Madicken Munk +(<a href="https://twitter.com/munkium">@munkium</a>), as well as +<a href="https://openteams.com">OpenTeams</a> and <a href="https://www.quansight.com/">QuanSight</a> +for having us.</p> + +<p>You can find all previous episodes of the Open Source Directions webinar +<a href="https://www.quansight.com/open-source-directions">here</a>.</p> + + + + + Announcing FortranCon 2020 + + 2020-04-06T00:00:00+03:00 + /news/newsletter/2020/04/06/Announcing-FortranCon-2020 + <p>FortranCon 2020, the first international conference targeting the Fortran +programming language, will take place on July 2-4, 2020, in Zürich, Switzerland.</p> + +<blockquote class="twitter-tweet"><p lang="en" dir="ltr">We&#39;re happy to announce the (to our knowledge first) International <a href="https://twitter.com/hashtag/Fortran?src=hash&amp;ref_src=twsrc%5Etfw">#Fortran</a> <a href="https://twitter.com/hashtag/Conference?src=hash&amp;ref_src=twsrc%5Etfw">#Conference</a> July 2.-4. at the <a href="https://twitter.com/UZH_en?ref_src=twsrc%5Etfw">@UZH_en</a> in <a href="https://twitter.com/hashtag/Zurich?src=hash&amp;ref_src=twsrc%5Etfw">#Zurich</a>, <a href="https://twitter.com/hashtag/Switzerland?src=hash&amp;ref_src=twsrc%5Etfw">#Switzerland</a> with <a href="https://twitter.com/DoctorFortran?ref_src=twsrc%5Etfw">@DoctorFortran</a> joining as keynote speaker! Call for presentations is open: <a href="https://t.co/LnyOZxHrZI">https://t.co/LnyOZxHrZI</a> <a href="https://twitter.com/hashtag/HPC?src=hash&amp;ref_src=twsrc%5Etfw">#HPC</a></p>&mdash; tizianomueller (@tizianomueller) <a href="https://twitter.com/tizianomueller/status/1247121616326348800?ref_src=twsrc%5Etfw">April 6, 2020</a></blockquote> +<script async="" src="https://platform.twitter.com/widgets.js" charset="utf-8"></script> + +<p>FortranCon aims to bring together developers of Fortran libraries, +applications, and language itself to share their experience and ideas. +The conference is organized in two full days of speaker presentations +on July 2 and 3, and a half-day workshop with lectures and hands-on sessions +on July 4. +Click <a href="https://tcevents.chem.uzh.ch/event/12/abstracts/">here</a> to submit +an abstract.</p> + +<p>The keynote presentation will be delivered by Steve Lionel +(<a href="https://twitter.com/doctorfortran">@doctorfortran</a>), convener of the +US Fortran Standards Committee.</p> + +<p>The <a href="https://tcevents.chem.uzh.ch/event/12/registrations/">registration</a> +is <strong>free of charge</strong>, with June 1, 2020 as the deadline. +Virtual participation will be enabled for speakers and attendees unable to +travel.</p> + +<p>Read more about FortranCon 2020 <a href="https://tcevents.chem.uzh.ch/event/12/">here</a>.</p> + + + + + J3 February 2020 Meeting + + 2020-02-28T00:00:00+02:00 + /news/newsletter/2020/02/28/J3-february-meeting + <p>The J3 Fortran Committee meeting took place in Las Vegas, NV, on February 24-28, +2020.</p> + +<h2 id="attendance">Attendance</h2> + +<p>The following people / companies attended:</p> + +<p>Voting members:</p> + +<ol> + <li>Intel: Jon Steidel</li> + <li>HPE/Cray: Bill Long</li> + <li>NVIDIA: Peter Klausler, Gary Klimowicz</li> + <li>IBM: Daniel Chen</li> + <li>ARM: Srinath Vadlamani</li> + <li>NCAR: Dan Nagle, Magne Haveraaen</li> + <li>NASA: Tom Clune</li> + <li>JPL: Van Sneider</li> + <li>LANL: Zach Jibben, Ondřej Čertík</li> + <li>ORNL: Reuben Budiardja</li> + <li>LBNL: Brian Friesen</li> + <li>Sandia: Damian Rouson</li> + <li>Lionel: Steven Lionel, Malcolm Cohen, Vipul Parekh</li> + <li>Corbett: Bob Corbett</li> +</ol> + +<p>Others:</p> + +<ol> + <li>AMD: Richard Bleikamp</li> + <li>WG23: Stephen Michell (convenor), Erhard Ploedereder (member)</li> + <li>Structural Integrity: Brad Richardson</li> +</ol> + +<h2 id="proposals-discussed-at-plenary">Proposals Discussed at Plenary</h2> + +<h3 id="monday-224">Monday 2/24</h3> + +<h3 id="tuesday-225">Tuesday 2/25</h3> + +<ul> + <li><a href="https://github.com/j3-fortran/fortran_proposals/issues/22">#22</a> : Default values of optional arguments (<a href="https://j3-fortran.org/doc/year/20/20-107.txt">https://j3-fortran.org/doc/year/20/20-107.txt</a>)</li> +</ul> + +<h3 id="wednesday-226">Wednesday 2/26</h3> + +<ul> + <li><a href="https://github.com/j3-fortran/fortran_proposals/issues/157">#157</a> : Rank-agnostic array element and section denotation (<a href="https://j3-fortran.org/doc/year/20/20-113.txt">https://j3-fortran.org/doc/year/20/20-113.txt</a>, <a href="https://j3-fortran.org/doc/year/20/20-115.txt">https://j3-fortran.org/doc/year/20/20-115.txt</a>)</li> + <li><a href="https://github.com/j3-fortran/fortran_proposals/issues/158">#158</a> : TYPEOF and CLASSOF (<a href="https://j3-fortran.org/doc/year/20/20-114.txt">https://j3-fortran.org/doc/year/20/20-114.txt</a>)</li> + <li><a href="https://github.com/j3-fortran/fortran_proposals/issues/1">#1</a> : Namespace for modules (<a href="https://j3-fortran.org/doc/year/20/20-108.txt">https://j3-fortran.org/doc/year/20/20-108.txt</a>)</li> + <li>Interpretation: FORM TEAM and failed images (<a href="https://j3-fortran.org/doc/year/20/20-102r1.txt">https://j3-fortran.org/doc/year/20/20-102r1.txt</a>)</li> + <li>Interpretation: Collective subroutines and STAT= (<a href="https://j3-fortran.org/doc/year/20/20-104r1.txt">https://j3-fortran.org/doc/year/20/20-104r1.txt</a>)</li> +</ul> + +<h3 id="thursday-227">Thursday 2/27</h3> + +<ul> + <li>Interpretation: events that cause variables to become undefined (<a href="https://j3-fortran.org/doc/year/20/20-119.txt">https://j3-fortran.org/doc/year/20/20-119.txt</a>)</li> + <li>Edits for SIMPLE procedures (<a href="https://j3-fortran.org/doc/year/20/20-116.txt">https://j3-fortran.org/doc/year/20/20-116.txt</a>)</li> + <li>BFLOAT16 (<a href="https://j3-fortran.org/doc/year/20/20-118.txt">https://j3-fortran.org/doc/year/20/20-118.txt</a>)</li> + <li><a href="https://github.com/j3-fortran/fortran_proposals/issues/146">#146</a> : Interpretation: allocatable component finalization (<a href="https://j3-fortran.org/doc/year/20/20-117.txt">https://j3-fortran.org/doc/year/20/20-117.txt</a>)</li> +</ul> + +<h3 id="friday-228">Friday 2/28</h3> + +<ul> + <li><a href="https://github.com/j3-fortran/fortran_proposals/issues/157">#157</a> : Rank-agnostic syntax (<a href="https://j3-fortran.org/doc/year/20/20-120.txt">https://j3-fortran.org/doc/year/20/20-120.txt</a>). Passed unanimously with minor changes.</li> + <li><a href="https://github.com/j3-fortran/fortran_proposals/issues/156">#156</a> : Protected components (<a href="https://j3-fortran.org/doc/year/20/20-121.txt">https://j3-fortran.org/doc/year/20/20-121.txt</a>). Withdrawn to address conflicting interests.</li> + <li><a href="https://github.com/j3-fortran/fortran_proposals/issues/160">#160</a> : Edits for auto-allocate characters (<a href="https://j3-fortran.org/doc/year/20/20-122.txt">https://j3-fortran.org/doc/year/20/20-122.txt</a>). Passed unanimously with minor changes.</li> + <li>Edits for procedure pointer association (<a href="https://j3-fortran.org/doc/year/20/20-123.txt">https://j3-fortran.org/doc/year/20/20-123.txt</a>). Passed unanimously.</li> + <li><a href="https://github.com/j3-fortran/fortran_proposals/issues/157">#157</a> : Edits for rank-agnostic bounds (<a href="https://j3-fortran.org/doc/year/20/20-124.txt">https://j3-fortran.org/doc/year/20/20-124.txt</a>). Withdrawn because some edits were missing and need to be added. There were concerns about fitting into the framework of generics later on.</li> + <li><a href="https://github.com/j3-fortran/fortran_proposals/issues/157">#157</a> : Edits for rank-agnostic array element and section denotation (<a href="https://j3-fortran.org/doc/year/20/20-125.txt">https://j3-fortran.org/doc/year/20/20-125.txt</a>). Failed (5 v 7). Missing edits, and disagreement on types vs rank-1 integers, the options need to be explored more.</li> + <li><a href="https://github.com/j3-fortran/fortran_proposals/issues/157">#157</a> : Edits for rank-agnostic allocation and pointer assignment (<a href="https://j3-fortran.org/doc/year/20/20-126.txt">https://j3-fortran.org/doc/year/20/20-126.txt</a>). Passed unanimously with minor changes.</li> + <li>Interpretation: Public namelist and private variable (<a href="https://j3-fortran.org/doc/year/20/20-127.txt">https://j3-fortran.org/doc/year/20/20-127.txt</a>). Straw vote (0 yes, 8 no, 9 undecided). Passed unanimously with “no” alternative.</li> + <li>Interpretation F18/015 (<a href="https://j3-fortran.org/doc/year/20/20-105.txt">https://j3-fortran.org/doc/year/20/20-105.txt</a>). Passed unanimously.</li> +</ul> + +<h2 id="skipped">Skipped</h2> + +<p>This was on the plan but we did not get to it:</p> + +<ul> + <li><a href="https://github.com/j3-fortran/fortran_proposals/issues/5">#5</a> : US 27 POINTER dummy arguments, INTENT, and target modification (<a href="https://j3-fortran.org/doc/year/18/18-144r1.txt">https://j3-fortran.org/doc/year/18/18-144r1.txt</a>)</li> + <li><a href="https://github.com/j3-fortran/fortran_proposals/issues/19">#19</a> : Short-circuiting proposal</li> +</ul> + +<h2 id="more-details">More Details</h2> + +<p>More details available at +<a href="https://github.com/j3-fortran/fortran_proposals/issues/155">j3-fortran/fortran_proposals #155</a> and at the official <a href="https://j3-fortran.org/doc/year/20/minutes221.txt">minutes</a> from the meeting.</p> + + + + + + diff --git a/_site/news/archive/index.html b/_site/news/archive/index.html new file mode 100644 index 000000000..b05a1e16e --- /dev/null +++ b/_site/news/archive/index.html @@ -0,0 +1,188 @@ + + + + + + + + News archive - Fortran Programming Language + + + + + + + + + + + + + + + + +
    +
    + + +
    +
    + + + + + + + + + + + + + diff --git a/_site/news/index.html b/_site/news/index.html new file mode 100644 index 000000000..192f2042d --- /dev/null +++ b/_site/news/index.html @@ -0,0 +1,741 @@ + + + + + + + + News - Fortran Programming Language + + + + + + + + + + + + + + + + +
    +
    + + +
    +

    News

    + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + +
    Fortran newsletter: June 2020   01 Jun 2020
    Fortran newsletter: May 2020   01 May 2020
    Open Source Directions Fortran webinar   18 Apr 2020
    Announcing FortranCon 2020   06 Apr 2020
    J3 February 2020 Meeting   28 Feb 2020
    +

    More…

    + +
    + + + + + + + +
    + +
    +
    + +
    +
    +
    + + See the + news archive for older posts +
    +
    + +
    + + + + + + + + + + + + + diff --git a/_site/newsletter/2020/02/28/J3-february-meeting/index.html b/_site/newsletter/2020/02/28/J3-february-meeting/index.html new file mode 100644 index 000000000..644c6c54d --- /dev/null +++ b/_site/newsletter/2020/02/28/J3-february-meeting/index.html @@ -0,0 +1,251 @@ + + + + + + + + J3 February 2020 Meeting - Fortran Programming Language + + + + + + + + + + + + + + + + +
    +
    + +
    +
    + + + + + + + + + + + + + diff --git a/_site/newsletter/2020/04/06/Announcing-FortranCon-2020/index.html b/_site/newsletter/2020/04/06/Announcing-FortranCon-2020/index.html new file mode 100644 index 000000000..7bb0f43fb --- /dev/null +++ b/_site/newsletter/2020/04/06/Announcing-FortranCon-2020/index.html @@ -0,0 +1,182 @@ + + + + + + + + Announcing FortranCon 2020 - Fortran Programming Language + + + + + + + + + + + + + + + + +
    +
    + +
    +
    + + + + + + + + + + + + + diff --git a/_site/newsletter/2020/04/18/Fortran-Webinar/index.html b/_site/newsletter/2020/04/18/Fortran-Webinar/index.html new file mode 100644 index 000000000..687461bcc --- /dev/null +++ b/_site/newsletter/2020/04/18/Fortran-Webinar/index.html @@ -0,0 +1,178 @@ + + + + + + + + Open Source Directions Fortran webinar - Fortran Programming Language + + + + + + + + + + + + + + + + +
    +
    + +
    +
    + + + + + + + + + + + + + diff --git a/_site/newsletter/2020/05/01/Fortran-Newsletter-May-2020/index.html b/_site/newsletter/2020/05/01/Fortran-Newsletter-May-2020/index.html new file mode 100644 index 000000000..f3680b7cf --- /dev/null +++ b/_site/newsletter/2020/05/01/Fortran-Newsletter-May-2020/index.html @@ -0,0 +1,295 @@ + + + + + + + + Fortran newsletter: May 2020 - Fortran Programming Language + + + + + + + + + + + + + + + + +
    +
    + +
    +
    + + + + + + + + + + + + + diff --git a/_site/newsletter/2020/06/01/Fortran-Newsletter-June-2020/index.html b/_site/newsletter/2020/06/01/Fortran-Newsletter-June-2020/index.html new file mode 100644 index 000000000..a41be1304 --- /dev/null +++ b/_site/newsletter/2020/06/01/Fortran-Newsletter-June-2020/index.html @@ -0,0 +1,300 @@ + + + + + + + + Fortran newsletter: June 2020 - Fortran Programming Language + + + + + + + + + + + + + + + + +
    +
    + +
    +
    + + + + + + + + + + + + + diff --git a/_site/packages/data-types.html b/_site/packages/data-types.html new file mode 100644 index 000000000..46c580f98 --- /dev/null +++ b/_site/packages/data-types.html @@ -0,0 +1,436 @@ + + + + + + + + Data types and containers - Fortran Programming Language + + + + + + + + + + + + + + + + +
    +

    Featured Open Source Projects

    +

    A rich ecosystem of high-performance code

    +
    + +
    +
    +
    + +

    Packages / + + + + Data types and containers

    +

    + Libraries for advanced data types and container classes +

    + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + +

    + + coretran

    + + + +
    + Core fortran routines and object-oriented classes for sorting, kD-Trees, and other algorithms to handle scientific data and concepts +
    + Tags: dynamic array formatting debugging errors kdtree sorting random binary search strings unit testing timing +

    + + Fortran template library

    + + + + + +
    + Generic containers, versatile algorithms, easy string manipulation, and more +
    + Tags: resizeable array container linked list hash map regex string shared pointer +

    + + PENF

    + + + +
    + Provides portable kind-parameters and many useful procedures to deal with them +
    + Tags: kinds integer real ieee floating point floats precision +

    + + M_time

    + + + +
    + Procedures that expand on the Fortran DATE_AND_TIME intrinsic +
    + Tags: date weekday unix epoch month convert moon phases duration +

    + + fdict

    + + + +
    + Variable and type-free dictionary +
    + Tags: hash table +

    + + kdtree2

    + + + +
    + A kd-tree implementation in fortran +
    + Tags: +

    + + datetime-fortran

    + + + +
    + Date and time manipulation +
    + Tags: day year month calendar weekday clock +

    + + qContainers

    + + + +
    + Store any intrinsic or derived data type to a container +
    + Tags: qlibc tree table hash table linked list vector dynamic array unique set +

    + + Lookup Table Fortran

    + + + +
    + Linear lookup table implemented in modern Fortran +
    + Tags: +

    + + + + + FyCollections

    + + + +
    + generic collection templates for Fortran +
    + Tags: +
    + +
    + +
    +
    + +
    +
    +
    + + + See + + here for how to get your project listed. + +
    +
    + + + + + + + + + + + + + diff --git a/_site/packages/examples.html b/_site/packages/examples.html new file mode 100644 index 000000000..1bd65a042 --- /dev/null +++ b/_site/packages/examples.html @@ -0,0 +1,283 @@ + + + + + + + + Examples and templates - Fortran Programming Language + + + + + + + + + + + + + + + + +
    +

    Featured Open Source Projects

    +

    A rich ecosystem of high-performance code

    +
    + +
    +
    +
    + +

    Packages / + + + + Examples and templates

    +

    + Demonstration codes and templates for Fortran +

    + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + +

    + + tcp-client-server

    + + + +
    + A minimal Fortran TCP client and server demonstrating c interoperability +
    + Tags: +

    + + Fortran 2018 examples

    + + + + + +
    + Easy examples of scientific computing with modern, powerful, easy Fortran 2018 standard +
    + Tags: block coarray contiguous mpi namelist openmp random submodule iso_fortran_env +

    + + Fortran patterns

    + + + +
    + Popular design patterns implemented in Fortran +
    + Tags: +

    + + Numerical methods in fortran

    + + + +
    + Solving linear, nonlinear equations, ordinary differential equations +
    + Tags: ode pde integral stochastic quadrature plotting +
    + +
    + +
    +
    + +
    +
    +
    + + + See + + here for how to get your project listed. + +
    +
    + + + + + + + + + + + + + diff --git a/_site/packages/graphics.html b/_site/packages/graphics.html new file mode 100644 index 000000000..73aae9d76 --- /dev/null +++ b/_site/packages/graphics.html @@ -0,0 +1,385 @@ + + + + + + + + Graphics, plotting and user interfaces - Fortran Programming Language + + + + + + + + + + + + + + + + +
    +

    Featured Open Source Projects

    +

    A rich ecosystem of high-performance code

    +
    + +
    +
    +
    + +

    Packages / + + + + Graphics, plotting and user interfaces

    +

    + Libraries for plotting data, handling images and generating user interfaces +

    + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + +

    + + + f03gl

    + + + +
    + Fortran 2003 interface to OpenGL +
    + Tags: graphics interface opengl +

    + + + PLplot

    + + + + + +
    + Library for scientific plotting +
    + Tags: plot surface contour interface +

    + + pyplot-fortran

    + + + +
    + For generating plots from Fortran using Python's matplotlib.pyplot +
    + Tags: pyplot matplotlib contour histogram +

    + + ogpf

    + + + +
    + Object based interface to GnuPlot for Fortran +
    + Tags: animation plot surface contour +

    + + gtk-fortran

    + + + +
    + A cross-platform library to build Graphical User Interfaces (GUI) +
    + Tags: gui gtk graphical user interface +

    + + M_draw

    + + + +
    + Low-level vector graphics library +
    + Tags: +

    + + fortran-xlib

    + + + +
    + A collection of ISO C binding interfaces to Xlib for Fortran 2003 +
    + Tags: x11 mandelbrot raycast wireframe +

    + + fortran-sdl2

    + + + +
    + A collection of ISO C binding interfaces to Simple DirectMedia Layer 2.0 (SDL 2.0), for multimedia and game programming in Fortran +
    + Tags: +
    + +
    + +
    +
    + +
    +
    +
    + + + See + + here for how to get your project listed. + +
    +
    + + + + + + + + + + + + + diff --git a/_site/packages/index.html b/_site/packages/index.html new file mode 100644 index 000000000..99d439325 --- /dev/null +++ b/_site/packages/index.html @@ -0,0 +1,566 @@ + + + + + + + + Fortran Packages - Fortran Programming Language + + + + + + + + + + + + + + + + +
    +

    Fortran Packages

    +

    A rich ecosystem of high-performance code

    +
    + +
    +
    +

    Fortran-lang community projects

    + +
    +

    + Fortran Standard Library (stdlib)

    +

    + A community-driven project for a de facto "standard" library for Fortran. + The stdlib project is both a specification and a reference implementation, developed in + cooperation with the Fortran Standards Committee. + Find out more on + + GitHub. +

    + + + + + + + + + + + + + +
    + +
    + + +
    +

    + Fortran Package Manager (fpm)

    +

    + A prototype project to develop a common build system for Fortran packages + and their dependencies. + Find out more on + + GitHub. +

    + + + + + + + + + + + + +
    + + +
    + +
    +

    + fortran-lang.org

    +

    + This website is open source and contributions are welcome! + Find out more on + + GitHub. +

    + + + + + + + + + + + + +
    + +
    + + +
    +
    + +
    +
    +

    Featured open source projects

    + +
    + + +
    + +

    Browse by category

    +
    + + + + + + + + + + + + + + + + + + + + + +
    +

    + + + + + Data types and containers + + (10) +

    +

    Libraries for advanced data types and container classes

    +
    + + + + + + + + + + + +
    +

    + + + + + Examples and templates + + (4) +

    +

    Demonstration codes and templates for Fortran

    +
    + + + + + + + +
    +

    + + + + + Graphics, plotting and user interfaces + + (8) +

    +

    Libraries for plotting data, handling images and generating user interfaces

    +
    + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + +
    +

    + + + + + Interface libraries + + (17) +

    +

    Libraries that interface with other systems, languages, or devices

    +
    + + + + + + + +
    +

    + + + + + Input, output and parsing + + (16) +

    +

    Libraries for reading, writing and parsing files and inputs

    +
    + + + + + + + +
    +

    + + + + + Libraries + + (9) +

    +

    Fortran libraries for general programming tasks

    +
    + + + + + + + + + + + +
    +

    + + + + + Numerical projects + + (21) +

    +

    Fortran libraries for linear algebra, optimization, root-finding etc.

    +
    + + + + + + + + + + + + + + + + + + + + + +
    +

    + + + + + Programming utilities + + (7) +

    +

    Error handling, logging, documentation and testing

    +
    + + + + + + + + + + + + + + + +
    +

    + + + + + Scientific Codes + + (16) +

    +

    Applications and libraries for applied mathematical and scientific problems

    +
    + + + + + + + + + + + +
    +

    + + + + + Characters and strings + + (5) +

    +

    Libraries for manipulating characters and strings

    +
    + + + + + + + + +
    +
    +
    + +
    +
    +
    + + See + + here for how to get your project listed. + +
    +
    + + + + + + + + + + + + + + diff --git a/_site/packages/interfaces.html b/_site/packages/interfaces.html new file mode 100644 index 000000000..c5b7605fd --- /dev/null +++ b/_site/packages/interfaces.html @@ -0,0 +1,620 @@ + + + + + + + + Interface libraries - Fortran Programming Language + + + + + + + + + + + + + + + + +
    +

    Featured Open Source Projects

    +

    A rich ecosystem of high-performance code

    +
    + +
    +
    +
    + +

    Packages / + + + + Interface libraries

    +

    + Libraries that interface with other systems, languages, or devices +

    + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + +

    + + forpy

    + + + + + +
    + allows you to use Python features in Fortran +
    + Tags: dict list tuple numpy python matplotlib scipy +

    + + tcp-client-server

    + + + +
    + A minimal Fortran TCP client and server demonstrating c interoperability +
    + Tags: +

    + + clfortran

    + + + + + +
    + Fortran interfaces to Khronos OpenCL 1.2 API +
    + Tags: gpu compute accelerator +

    + + M_process

    + + + +
    + Read and write lines to or from a process from Fortran via a C wrapper +
    + Tags: +

    + + M_system

    + + + +
    + Call C system routines from Fortran +
    + Tags: posix putenv getenv setenv environment file system mkdir rename rmdir chmod rand uname +

    + + Focal

    + + + +
    + A module library which wraps calls to the OpenCL runtime API with a higher abstraction level +
    + Tags: gpu compute accelerator +

    + + + + + foryxima

    + + + +
    + File system manipulation and unit testing framework +
    + Tags: posix libc +

    + + + + + sqliteff

    + + + +
    + A thin wrapper around the SQLite library +
    + Tags: sql database +

    + + + f03gl

    + + + +
    + Fortran 2003 interface to OpenGL +
    + Tags: graphics interface opengl +

    + + + PLplot

    + + + + + +
    + Library for scientific plotting +
    + Tags: plot surface contour interface +

    + + pyplot-fortran

    + + + +
    + For generating plots from Fortran using Python's matplotlib.pyplot +
    + Tags: pyplot matplotlib contour histogram +

    + + ogpf

    + + + +
    + Object based interface to GnuPlot for Fortran +
    + Tags: animation plot surface contour +

    + + gtk-fortran

    + + + +
    + A cross-platform library to build Graphical User Interfaces (GUI) +
    + Tags: gui gtk graphical user interface +

    + + fortran-xlib

    + + + +
    + A collection of ISO C binding interfaces to Xlib for Fortran 2003 +
    + Tags: x11 mandelbrot raycast wireframe +

    + + fortran-sdl2

    + + + +
    + A collection of ISO C binding interfaces to Simple DirectMedia Layer 2.0 (SDL 2.0), for multimedia and game programming in Fortran +
    + Tags: +

    + + fortranlib

    + + + +
    + Collection of personal scientific routines in Fortran +
    + Tags: solver integral integrate interpolation histogram constants hdf5 error random posix angles probability stokes vectors +

    + + fgsl

    + + + +
    + Fortran interface to the GNU Scientific Library +
    + Tags: +
    + +
    + +
    +
    + +
    +
    +
    + + + See + + here for how to get your project listed. + +
    +
    + + + + + + + + + + + + + diff --git a/_site/packages/io.html b/_site/packages/io.html new file mode 100644 index 000000000..94fbdd96a --- /dev/null +++ b/_site/packages/io.html @@ -0,0 +1,589 @@ + + + + + + + + Input, output and parsing - Fortran Programming Language + + + + + + + + + + + + + + + + +
    +

    Featured Open Source Projects

    +

    A rich ecosystem of high-performance code

    +
    + +
    +
    +
    + +

    Packages / + + + + Input, output and parsing

    +

    + Libraries for reading, writing and parsing files and inputs +

    + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + +

    + + fortran-utils

    + + + +
    + Various utilities for Fortran programs +
    + Tags: constants types sorting mesh spline ppm hdf5 lapack +

    + + json-fortran

    + + + +
    + A Fortran 2008 JSON API +
    + Tags: json io +

    + + VTKFortran

    + + + +
    + Library to parse and emit files conforming VTK (XML) standard +
    + Tags: +

    + + netCFD-Fortran

    + + + +
    + Fortran interfaces for netCFD C library. +
    + Tags: netcdf +

    + + fox

    + + + +
    + A Fortran XML library +
    + Tags: +

    + + FEconv

    + + + +
    + utility and library for converting between mesh and finite element field formats +
    + Tags: ansys msh nastran bdf vtk +

    + + h5fortran

    + + + +
    + Simple, robust, thin HDF5 polymorphic read/write interface +
    + Tags: hdf5 +

    + + nc4fortran

    + + + +
    + Object-oriented interface for NetCDF4 in Fortran +
    + Tags: netcdf +

    + + fortran-csv-module

    + + + +
    + Read and write CSV Files using modern Fortran +
    + Tags: +

    + + M_IO

    + + + + + +
    + Fortran module for common I/O tasks +
    + Tags: delete slurp swallow dirname split path +

    + + + + + jsonff

    + + + +
    + Routines for building JSON structures in Fortran +
    + Tags: +

    + + NPY for Fortran

    + + + +
    + Allows saving numerical Fortran arrays in Numpy's .npy or .npz format +
    + Tags: python +

    + + FiNeR

    + + + +
    + INI ParseR and generator +
    + Tags: config +

    + + config_fortran

    + + + +
    + Configuration file parser for Fortran +
    + Tags: +

    + + + + + Parser for Fortran

    + + + +
    + The foundations of a functional style parser combinator library +
    + Tags: +

    + + fortranlib

    + + + +
    + Collection of personal scientific routines in Fortran +
    + Tags: solver integral integrate interpolation histogram constants hdf5 error random posix angles probability stokes vectors +
    + +
    + +
    +
    + +
    +
    +
    + + + See + + here for how to get your project listed. + +
    +
    + + + + + + + + + + + + + diff --git a/_site/packages/libraries.html b/_site/packages/libraries.html new file mode 100644 index 000000000..1d88672df --- /dev/null +++ b/_site/packages/libraries.html @@ -0,0 +1,406 @@ + + + + + + + + Libraries - Fortran Programming Language + + + + + + + + + + + + + + + + +
    +

    Featured Open Source Projects

    +

    A rich ecosystem of high-performance code

    +
    + +
    +
    +
    + +

    Packages / + + + + Libraries

    +

    + Fortran libraries for general programming tasks +

    + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + +

    + + functional-fortran

    + + + +
    + Functional programming for modern Fortran +
    + Tags: functional filter fold map +

    + + fortran-utils

    + + + +
    + Various utilities for Fortran programs +
    + Tags: constants types sorting mesh spline ppm hdf5 lapack +

    + + Open Coarrays

    + + + +
    + A parallel application binary interface for Fortran 2018 compilers. +
    + Tags: mpi openshmem gfortran +

    + + FLAP

    + + + +
    + Fortran command Line Arguments Parser +
    + Tags: command line cli argument parser +

    + + Fortran Standard Library (stdlib)

    + + + +
    + A community driven and agreed upon de facto standard library for Fortran +
    + Tags: +

    + + coretran

    + + + +
    + Core fortran routines and object-oriented classes for sorting, kD-Trees, and other algorithms to handle scientific data and concepts +
    + Tags: dynamic array formatting debugging errors kdtree sorting random binary search strings unit testing timing +

    + + M_CLI

    + + + +
    + Unix-like command line argument parsing +
    + Tags: namelist args +

    + + M_history

    + + + +
    + Subroutine to give a line-mode command history to interactive programs +
    + Tags: redo +

    + + fortranlib

    + + + +
    + Collection of personal scientific routines in Fortran +
    + Tags: solver integral integrate interpolation histogram constants hdf5 error random posix angles probability stokes vectors +
    + +
    + +
    +
    + +
    +
    +
    + + + See + + here for how to get your project listed. + +
    +
    + + + + + + + + + + + + + diff --git a/_site/packages/numerical.html b/_site/packages/numerical.html new file mode 100644 index 000000000..c7648449d --- /dev/null +++ b/_site/packages/numerical.html @@ -0,0 +1,721 @@ + + + + + + + + Numerical projects - Fortran Programming Language + + + + + + + + + + + + + + + + +
    +

    Featured Open Source Projects

    +

    A rich ecosystem of high-performance code

    +
    + +
    +
    +
    + +

    Packages / + + + + Numerical projects

    +

    + Fortran libraries for linear algebra, optimization, root-finding etc. +

    + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + +

    + + PENF

    + + + +
    + Provides portable kind-parameters and many useful procedures to deal with them +
    + Tags: kinds integer real ieee floating point floats precision +

    + + OpenBLAS

    + + + +
    + Optimized BLAS library based on GotoBLAS2 +
    + Tags: blas linear algebra +

    + + LAPACK

    + + + + + +
    + Routines for numerical linear algebra +
    + Tags: blas linear algera +

    + + ElmerFEM

    + + + +
    + Finite element software for numerical solution of partial differential equations +
    + Tags: pde fe +

    + + fortranlib

    + + + +
    + Collection of personal scientific routines in Fortran +
    + Tags: solver integral integrate interpolation histogram constants hdf5 error random posix angles probability stokes vectors +

    + + SHTOOLS

    + + + +
    + A Fortran-95/Python library that can be used to perform spherical harmonic transforms +
    + Tags: spectral analysis Slepian bases gravitational magnetic field openmp +

    + + ARPACK

    + + + + + +
    + Collection of Fortran77 subroutines designed to solve large scale eigenvalue problems. +
    + Tags: eigenvalue eigenvector singular value decomposition svd +

    + + neural-fortran

    + + + +
    + A parallel neural net microframework. +
    + Tags: back propagation coarray +

    + + ParaMonte

    + + + + + +
    + A general-purpose high-performance MPI/Coarray-parallel Monte Carlo simulation library implemented in Fortran 2018 with interfaces to C/C++/Fortran/MATLAB/Python +
    + Tags: parallel mpi coarray monte carlo mcmc c cpp matlab python statistics bayesian stochastic optimization sampling integration machine learning +

    + + bspline-fortran

    + + + +
    + Multidimensional B-Spline interpolation of data on a regular grid +
    + Tags: spline interpolation extrapolation integration integral +

    + + FOODIE

    + + + +
    + Fortran Object-Oriented Differential-equations Integration Environment +
    + Tags: ode pde euler runge kutta +

    + + fgsl

    + + + +
    + Fortran interface to the GNU Scientific Library +
    + Tags: +

    + + SciFortran

    + + + +
    + collection of fortran modules and procedures for scientific calculations. +
    + Tags: +

    + + Los Alamos Grid Toolbox (LaGriT)

    + + + + + +
    + a library of user callable tools that provide mesh generation, mesh optimization and dynamic mesh maintenance +
    + Tags: +

    + + DBCSR

    + + + +
    + Distributed block compresseed sparse row matrix library +
    + Tags: linear algebra parallel mpi openmp cuda hip +

    + + GALAHAD

    + + + + + +
    + Modules for nonlinear optimization +
    + Tags: least squares active set quadratic programming interior point convex programming linear programming +

    + + slsqp

    + + + +
    + SLSQP nonlinear constrained optimizer +
    + Tags: nonlinear programming equality inequality constraints +

    + + NumDiff

    + + + +
    + a modern Fortran interface for computing the Jacobian (derivative) matrix of m nonlinear functions which depend on n variables +
    + Tags: finite difference +

    + + + + + quaff

    + + + +
    + Quantities for Fortran. Make math with units more convenient +
    + Tags: +

    + + rng_fortran

    + + + + + +
    + Pseudo random number generator in Fortran, internally using xoroshiro128+ +
    + Tags: uniform normal poisson distributed +

    + + Numerical methods in fortran

    + + + +
    + Solving linear, nonlinear equations, ordinary differential equations +
    + Tags: ode pde integral stochastic quadrature plotting +
    + +
    + +
    +
    + +
    +
    +
    + + + See + + here for how to get your project listed. + +
    +
    + + + + + + + + + + + + + diff --git a/_site/packages/preview.html b/_site/packages/preview.html new file mode 100644 index 000000000..f8496a7ec --- /dev/null +++ b/_site/packages/preview.html @@ -0,0 +1,204 @@ + + + + + + + + Preview - Fortran Programming Language + + + + + + + + + + + + + + + + +
    +

    Featured Open Source Projects

    +

    A rich ecosystem of high-performance code

    +
    + +
    +
    +
    + +

    Packages / + + Preview

    +

    + Preview project badges +

    + + + + + + + + + + + + + + + + + + + + + +

    + + FORD

    + + + +
    + Automatic documentation generator for modern Fortran programs +
    + Tags: documentation +
    + +
    + +
    +
    + +
    +
    +
    + + + See + + here for how to get your project listed. + +
    +
    + + + + + + + + + + + + + diff --git a/_site/packages/programming.html b/_site/packages/programming.html new file mode 100644 index 000000000..b4483eda9 --- /dev/null +++ b/_site/packages/programming.html @@ -0,0 +1,370 @@ + + + + + + + + Programming utilities - Fortran Programming Language + + + + + + + + + + + + + + + + +
    +

    Featured Open Source Projects

    +

    A rich ecosystem of high-performance code

    +
    + +
    +
    +
    + +

    Packages / + + + + Programming utilities

    +

    + Error handling, logging, documentation and testing +

    + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + +

    + + coretran

    + + + +
    + Core fortran routines and object-oriented classes for sorting, kD-Trees, and other algorithms to handle scientific data and concepts +
    + Tags: dynamic array formatting debugging errors kdtree sorting random binary search strings unit testing timing +

    + + + + + foryxima

    + + + +
    + File system manipulation and unit testing framework +
    + Tags: posix libc +

    + + FORD

    + + + +
    + Automatic documentation generator for modern Fortran programs +
    + Tags: documentation +

    + + + + + vegetables

    + + + + + +
    + A Fortran testing framework written using functional programming principles. +
    + Tags: testing assert +

    + + pFUnit

    + + + +
    + Parallel Fortran Unit Testing Framework +
    + Tags: unit testing +

    + + + + + erloff

    + + + +
    + Errors and logging for fortran +
    + Tags: errors logging +

    + + + + + fytest

    + + + +
    + a lightweight unit testing framework for Fortran +
    + Tags: unit testing +
    + +
    + +
    +
    + +
    +
    +
    + + + See + + here for how to get your project listed. + +
    +
    + + + + + + + + + + + + + diff --git a/_site/packages/projects_json.js b/_site/packages/projects_json.js new file mode 100644 index 000000000..e7a575702 --- /dev/null +++ b/_site/packages/projects_json.js @@ -0,0 +1,953 @@ +projects = [ + + { + "name": "functional-fortran", + "description": "Functional programming for modern Fortran", + "github": "wavebitscientific/functional-fortran", + "url": "", + "categories": "libraries", + "tags": "functional filter fold map", + "license": "" + }, + + { + "name": "fortran-utils", + "description": "Various utilities for Fortran programs", + "github": "certik/fortran-utils", + "url": "", + "categories": "libraries io", + "tags": "constants types sorting mesh spline ppm hdf5 lapack", + "license": "" + }, + + { + "name": "Open Coarrays", + "description": "A parallel application binary interface for Fortran 2018 compilers.", + "github": "sourceryinstitute/OpenCoarrays", + "url": "", + "categories": "libraries", + "tags": "mpi openshmem gfortran", + "license": "" + }, + + { + "name": "FLAP", + "description": "Fortran command Line Arguments Parser", + "github": "szaghi/FLAP", + "url": "", + "categories": "libraries", + "tags": "command line cli argument parser", + "license": "none" + }, + + { + "name": "Fortran Standard Library (stdlib)", + "description": "A community driven and agreed upon de facto standard library for Fortran", + "github": "fortran-lang/stdlib", + "url": "", + "categories": "libraries", + "tags": "", + "license": "" + }, + + { + "name": "coretran", + "description": "Core fortran routines and object-oriented classes for sorting, kD-Trees, and other algorithms to handle scientific data and concepts", + "github": "leonfoks/coretran", + "url": "", + "categories": "libraries strings data-types programming", + "tags": "dynamic array formatting debugging errors kdtree sorting random binary search strings unit testing timing", + "license": "" + }, + + { + "name": "M_CLI", + "description": "Unix-like command line argument parsing", + "github": "urbanjost/M_CLI", + "url": "", + "categories": "libraries", + "tags": "namelist args", + "license": "" + }, + + { + "name": "M_history", + "description": "Subroutine to give a line-mode command history to interactive programs", + "github": "urbanjost/M_history", + "url": "", + "categories": "libraries", + "tags": "redo", + "license": "" + }, + + { + "name": "forpy", + "description": "allows you to use Python features in Fortran", + "github": "ylikx/forpy", + "url": "", + "categories": "interfaces", + "tags": "dict list tuple numpy python matplotlib scipy", + "license": "GNU GPL v3" + }, + + { + "name": "tcp-client-server", + "description": "A minimal Fortran TCP client and server demonstrating c interoperability", + "github": "modern-fortran/tcp-client-server", + "url": "", + "categories": "interfaces examples", + "tags": "", + "license": "" + }, + + { + "name": "clfortran", + "description": "Fortran interfaces to Khronos OpenCL 1.2 API", + "github": "cass-support/clfortran", + "url": "", + "categories": "interfaces", + "tags": "gpu compute accelerator", + "license": "GNU GPL v3" + }, + + { + "name": "M_process", + "description": "Read and write lines to or from a process from Fortran via a C wrapper", + "github": "urbanjost/M_process", + "url": "", + "categories": "interfaces", + "tags": "", + "license": "" + }, + + { + "name": "M_system", + "description": "Call C system routines from Fortran", + "github": "urbanjost/M_system", + "url": "", + "categories": "interfaces", + "tags": "posix putenv getenv setenv environment file system mkdir rename rmdir chmod rand uname", + "license": "" + }, + + { + "name": "Focal", + "description": "A module library which wraps calls to the OpenCL runtime API with a higher abstraction level", + "github": "LKedward/focal", + "url": "", + "categories": "interfaces", + "tags": "gpu compute accelerator", + "license": "" + }, + + { + "name": "foryxima", + "description": "File system manipulation and unit testing framework", + "github": "", + "url": "https://bitbucket.org/aradi/fortyxima/src/develop/", + "categories": "interfaces programming", + "tags": "posix libc", + "license": "BSD 2-clause" + }, + + { + "name": "sqliteff", + "description": "A thin wrapper around the SQLite library", + "github": "", + "url": "https://gitlab.com/everythingfunctional/sqliteff", + "categories": "interfaces", + "tags": "sql database", + "license": "MIT" + }, + + { + "name": "FORD", + "description": "Automatic documentation generator for modern Fortran programs", + "github": "Fortran-FOSS-Programmers/ford", + "url": "", + "categories": "programming preview", + "tags": "documentation", + "license": "" + }, + + { + "name": "vegetables", + "description": "A Fortran testing framework written using functional programming principles.", + "github": "", + "url": "https://gitlab.com/everythingfunctional/vegetables", + "categories": "programming", + "tags": "testing assert", + "license": "MIT" + }, + + { + "name": "pFUnit", + "description": "Parallel Fortran Unit Testing Framework", + "github": "Goddard-Fortran-Ecosystem/pFUnit", + "url": "", + "categories": "programming", + "tags": "unit testing", + "license": "none" + }, + + { + "name": "erloff", + "description": "Errors and logging for fortran", + "github": "", + "url": "https://gitlab.com/everythingfunctional/erloff", + "categories": "programming", + "tags": "errors logging", + "license": "BSD 3-Clause" + }, + + { + "name": "fytest", + "description": "a lightweight unit testing framework for Fortran", + "github": "", + "url": "https://bitbucket.org/aradi/fytest/src/develop/", + "categories": "programming", + "tags": "unit testing", + "license": "BSD 2-clause" + }, + + { + "name": "Fortran template library", + "description": "Generic containers, versatile algorithms, easy string manipulation, and more", + "github": "SCM-NV/ftl", + "url": "", + "categories": "data-types", + "tags": "resizeable array container linked list hash map regex string shared pointer", + "license": "GNU GPL v3" + }, + + { + "name": "PENF", + "description": "Provides portable kind-parameters and many useful procedures to deal with them", + "github": "szaghi/PENF", + "url": "", + "categories": "data-types numerical", + "tags": "kinds integer real ieee floating point floats precision", + "license": "none" + }, + + { + "name": "M_time", + "description": "Procedures that expand on the Fortran DATE_AND_TIME intrinsic", + "github": "urbanjost/M_time", + "url": "", + "categories": "data-types", + "tags": "date weekday unix epoch month convert moon phases duration", + "license": "" + }, + + { + "name": "fdict", + "description": "Variable and type-free dictionary", + "github": "zerothi/fdict", + "url": "", + "categories": "data-types", + "tags": "hash table", + "license": "" + }, + + { + "name": "kdtree2", + "description": "A kd-tree implementation in fortran", + "github": "jmhodges/kdtree2", + "url": "", + "categories": "data-types", + "tags": "", + "license": "none" + }, + + { + "name": "datetime-fortran", + "description": "Date and time manipulation", + "github": "wavebitscientific/datetime-fortran", + "url": "", + "categories": "data-types", + "tags": "day year month calendar weekday clock", + "license": "none" + }, + + { + "name": "qContainers", + "description": "Store any intrinsic or derived data type to a container", + "github": "darmar-lt/qcontainers", + "url": "", + "categories": "data-types", + "tags": "qlibc tree table hash table linked list vector dynamic array unique set", + "license": "none" + }, + + { + "name": "Lookup Table Fortran", + "description": "Linear lookup table implemented in modern Fortran", + "github": "jannisteunissen/lookup_table_fortran", + "url": "", + "categories": "data-types", + "tags": "", + "license": "" + }, + + { + "name": "FyCollections", + "description": "generic collection templates for Fortran", + "github": "", + "url": "https://bitbucket.org/aradi/fycollections/src/develop/", + "categories": "data-types", + "tags": "", + "license": "BSD 2-Clause" + }, + + { + "name": "StringiFor", + "description": "Fortran strings manipulator", + "github": "szaghi/StringiFor", + "url": "", + "categories": "strings", + "tags": "split join basename search concat", + "license": "none" + }, + + { + "name": "M_strings", + "description": "Fortran string manipulations", + "github": "urbanjost/M_strings", + "url": "", + "categories": "strings", + "tags": "upper lower quoted join replace white space string conversion tokens split", + "license": "" + }, + + { + "name": "Strings for Fortran", + "description": "A library of string functions for Fortran.", + "github": "", + "url": "https://gitlab.com/everythingfunctional/strff", + "categories": "strings", + "tags": "", + "license": "MIT" + }, + + { + "name": "iso_varying_string", + "description": "Implementation of the Fortran ISO_VARYING_STRING module in accordance with the standard", + "github": "", + "url": "https://gitlab.com/everythingfunctional/iso_varying_string", + "categories": "strings", + "tags": "varying length character strings", + "license": "MIT" + }, + + { + "name": "json-fortran", + "description": "A Fortran 2008 JSON API", + "github": "jacobwilliams/json-fortran", + "url": "", + "categories": "io", + "tags": "json io", + "license": "none" + }, + + { + "name": "VTKFortran", + "description": "Library to parse and emit files conforming VTK (XML) standard", + "github": "szaghi/VTKFortran", + "url": "", + "categories": "io", + "tags": "", + "license": "none" + }, + + { + "name": "netCFD-Fortran", + "description": "Fortran interfaces for netCFD C library.", + "github": "Unidata/netcdf-fortran", + "url": "", + "categories": "io", + "tags": "netcdf", + "license": "none" + }, + + { + "name": "fox", + "description": "A Fortran XML library", + "github": "andreww/fox", + "url": "", + "categories": "io", + "tags": "", + "license": "none" + }, + + { + "name": "FEconv", + "description": "utility and library for converting between mesh and finite element field formats", + "github": "victorsndvg/FEconv", + "url": "", + "categories": "io", + "tags": "ansys msh nastran bdf vtk", + "license": "" + }, + + { + "name": "h5fortran", + "description": "Simple, robust, thin HDF5 polymorphic read/write interface", + "github": "scivision/h5fortran", + "url": "", + "categories": "io", + "tags": "hdf5", + "license": "" + }, + + { + "name": "nc4fortran", + "description": "Object-oriented interface for NetCDF4 in Fortran", + "github": "scivision/nc4fortran", + "url": "", + "categories": "io", + "tags": "netcdf", + "license": "" + }, + + { + "name": "fortran-csv-module", + "description": "Read and write CSV Files using modern Fortran", + "github": "jacobwilliams/fortran-csv-module", + "url": "", + "categories": "io", + "tags": "", + "license": "none" + }, + + { + "name": "M_IO", + "description": "Fortran module for common I/O tasks", + "github": "urbanjost/M_io", + "url": "", + "categories": "io", + "tags": "delete slurp swallow dirname split path", + "license": "Public domain" + }, + + { + "name": "jsonff", + "description": "Routines for building JSON structures in Fortran", + "github": "", + "url": "https://gitlab.com/everythingfunctional/jsonff", + "categories": "io", + "tags": "", + "license": "MIT" + }, + + { + "name": "NPY for Fortran", + "description": "Allows saving numerical Fortran arrays in Numpy's .npy or .npz format", + "github": "MRedies/NPY-for-Fortran", + "url": "", + "categories": "io", + "tags": "python", + "license": "" + }, + + { + "name": "FiNeR", + "description": "INI ParseR and generator", + "github": "szaghi/FiNeR", + "url": "", + "categories": "io", + "tags": "config", + "license": "none" + }, + + { + "name": "config_fortran", + "description": "Configuration file parser for Fortran", + "github": "jannisteunissen/config_fortran", + "url": "", + "categories": "io", + "tags": "", + "license": "" + }, + + { + "name": "Parser for Fortran", + "description": "The foundations of a functional style parser combinator library", + "github": "", + "url": "https://gitlab.com/everythingfunctional/parff", + "categories": "io", + "tags": "", + "license": "MIT" + }, + + { + "name": "f03gl", + "description": "Fortran 2003 interface to OpenGL", + "github": "", + "url": "http://www-stone.ch.cam.ac.uk/pub/f03gl/index.xhtml", + "categories": "graphics interfaces", + "tags": "graphics interface opengl", + "license": "GNU GPL v3" + }, + + { + "name": "PLplot", + "description": "Library for scientific plotting", + "github": "", + "url": "http://plplot.sourceforge.net/", + "categories": "graphics interfaces", + "tags": "plot surface contour interface", + "license": "GNU LGPL v3" + }, + + { + "name": "pyplot-fortran", + "description": "For generating plots from Fortran using Python's matplotlib.pyplot", + "github": "jacobwilliams/pyplot-fortran", + "url": "", + "categories": "graphics interfaces", + "tags": "pyplot matplotlib contour histogram", + "license": "none" + }, + + { + "name": "ogpf", + "description": "Object based interface to GnuPlot for Fortran", + "github": "kookma/ogpf", + "url": "", + "categories": "graphics interfaces", + "tags": "animation plot surface contour", + "license": "none" + }, + + { + "name": "gtk-fortran", + "description": "A cross-platform library to build Graphical User Interfaces (GUI)", + "github": "vmagnin/gtk-fortran", + "url": "", + "categories": "graphics interfaces", + "tags": "gui gtk graphical user interface", + "license": "" + }, + + { + "name": "M_draw", + "description": "Low-level vector graphics library", + "github": "urbanjost/M_draw", + "url": "", + "categories": "graphics", + "tags": "", + "license": "" + }, + + { + "name": "fortran-xlib", + "description": "A collection of ISO C binding interfaces to Xlib for Fortran 2003", + "github": "interkosmos/fortran-xlib", + "url": "", + "categories": "graphics interfaces", + "tags": "x11 mandelbrot raycast wireframe", + "license": "" + }, + + { + "name": "fortran-sdl2", + "description": "A collection of ISO C binding interfaces to Simple DirectMedia Layer 2.0 (SDL 2.0), for multimedia and game programming in Fortran", + "github": "interkosmos/fortran-sdl2", + "url": "", + "categories": "graphics interfaces", + "tags": "", + "license": "" + }, + + { + "name": "OpenBLAS", + "description": "Optimized BLAS library based on GotoBLAS2", + "github": "xianyi/OpenBLAS", + "url": "", + "categories": "numerical", + "tags": "blas linear algebra", + "license": "" + }, + + { + "name": "LAPACK", + "description": "Routines for numerical linear algebra", + "github": "Reference-LAPACK/lapack", + "url": "", + "categories": "numerical", + "tags": "blas linear algera", + "license": "BSD 3-Clause" + }, + + { + "name": "ElmerFEM", + "description": "Finite element software for numerical solution of partial differential equations", + "github": "ElmerCSC/elmerfem", + "url": "", + "categories": "numerical", + "tags": "pde fe", + "license": "" + }, + + { + "name": "fortranlib", + "description": "Collection of personal scientific routines in Fortran", + "github": "astrofrog/fortranlib", + "url": "", + "categories": "libraries numerical io interfaces", + "tags": "solver integral integrate interpolation histogram constants hdf5 error random posix angles probability stokes vectors", + "license": "" + }, + + { + "name": "SHTOOLS", + "description": "A Fortran-95/Python library that can be used to perform spherical harmonic transforms", + "github": "SHTOOLS/SHTOOLS", + "url": "", + "categories": "numerical", + "tags": "spectral analysis Slepian bases gravitational magnetic field openmp", + "license": "" + }, + + { + "name": "ARPACK", + "description": "Collection of Fortran77 subroutines designed to solve large scale eigenvalue problems.", + "github": "opencollab/arpack-ng", + "url": "", + "categories": "numerical", + "tags": "eigenvalue eigenvector singular value decomposition svd", + "license": "BSD 3-Clause" + }, + + { + "name": "neural-fortran", + "description": "A parallel neural net microframework.", + "github": "modern-fortran/neural-fortran", + "url": "", + "categories": "numerical", + "tags": "back propagation coarray", + "license": "" + }, + + { + "name": "ParaMonte", + "description": "A general-purpose high-performance MPI/Coarray-parallel Monte Carlo simulation library implemented in Fortran 2018 with interfaces to C/C++/Fortran/MATLAB/Python", + "github": "cdslaborg/paramonte", + "url": "", + "categories": "numerical", + "tags": "parallel mpi coarray monte carlo mcmc c cpp matlab python statistics bayesian stochastic optimization sampling integration machine learning", + "license": "" + }, + + { + "name": "bspline-fortran", + "description": "Multidimensional B-Spline interpolation of data on a regular grid", + "github": "jacobwilliams/bspline-fortran", + "url": "", + "categories": "numerical", + "tags": "spline interpolation extrapolation integration integral", + "license": "none" + }, + + { + "name": "FOODIE", + "description": "Fortran Object-Oriented Differential-equations Integration Environment", + "github": "Fortran-FOSS-Programmers/FOODIE", + "url": "", + "categories": "numerical", + "tags": "ode pde euler runge kutta", + "license": "none" + }, + + { + "name": "fgsl", + "description": "Fortran interface to the GNU Scientific Library", + "github": "reinh-bader/fgsl", + "url": "", + "categories": "numerical interfaces", + "tags": "", + "license": "" + }, + + { + "name": "SciFortran", + "description": "collection of fortran modules and procedures for scientific calculations.", + "github": "aamaricci/SciFortran", + "url": "", + "categories": "numerical", + "tags": "", + "license": "" + }, + + { + "name": "Los Alamos Grid Toolbox (LaGriT)", + "description": "a library of user callable tools that provide mesh generation, mesh optimization and dynamic mesh maintenance", + "github": "lanl/LaGriT", + "url": "", + "categories": "numerical", + "tags": "", + "license": "BSD" + }, + + { + "name": "DBCSR", + "description": "Distributed block compresseed sparse row matrix library", + "github": "cp2k/dbcsr", + "url": "", + "categories": "numerical", + "tags": "linear algebra parallel mpi openmp cuda hip", + "license": "" + }, + + { + "name": "GALAHAD", + "description": "Modules for nonlinear optimization", + "github": "ralna/GALAHAD", + "url": "", + "categories": "numerical", + "tags": "least squares active set quadratic programming interior point convex programming linear programming", + "license": "GNU LGPL v3" + }, + + { + "name": "slsqp", + "description": "SLSQP nonlinear constrained optimizer", + "github": "jacobwilliams/slsqp", + "url": "", + "categories": "numerical", + "tags": "nonlinear programming equality inequality constraints", + "license": "none" + }, + + { + "name": "NumDiff", + "description": "a modern Fortran interface for computing the Jacobian (derivative) matrix of m nonlinear functions which depend on n variables", + "github": "jacobwilliams/NumDiff", + "url": "", + "categories": "numerical", + "tags": "finite difference", + "license": "none" + }, + + { + "name": "quaff", + "description": "Quantities for Fortran. Make math with units more convenient", + "github": "", + "url": "https://gitlab.com/everythingfunctional/quaff", + "categories": "numerical", + "tags": "", + "license": "MIT" + }, + + { + "name": "rng_fortran", + "description": "Pseudo random number generator in Fortran, internally using xoroshiro128+", + "github": "jannisteunissen/rng_fortran", + "url": "", + "categories": "numerical", + "tags": "uniform normal poisson distributed", + "license": "GNU GPL v3" + }, + + { + "name": "WRF", + "description": "Weather Research and Forecasting model", + "github": "wrf-model/WRF", + "url": "", + "categories": "scientific", + "tags": "", + "license": "Public domain" + }, + + { + "name": "fds", + "description": "Large-eddy simulation code for low-speed flows, with an emphasis on smoke and heat transport from fires.", + "github": "firemodels/fds", + "url": "", + "categories": "scientific", + "tags": "", + "license": "none" + }, + + { + "name": "Quantum ESPRESSO", + "description": "Quantum ESPRESSO is an integrated suite of Open-Source computer codes for electronic-structure calculations and materials modeling at the nanoscale", + "github": "QEF/q-e", + "url": "", + "categories": "scientific", + "tags": "electronic structure calculations quantum chemistry physics molecular dynamics mpi", + "license": "" + }, + + { + "name": "fluidity", + "description": "Computational fluid dynamics code with adaptive unstructured mesh capabilities", + "github": "FluidityProject/fluidity", + "url": "", + "categories": "scientific", + "tags": "cfd computational fluid dynamics unstructured", + "license": "" + }, + + { + "name": "fortran-machine", + "description": "", + "github": "mapmeld/fortran-machine", + "url": "", + "categories": "other", + "tags": "", + "license": "" + }, + + { + "name": "Nek5000", + "description": "MPI parallel higher-order spectral element CFD solver", + "github": "Nek5000/Nek5000", + "url": "", + "categories": "scientific", + "tags": "cfd computational fluid dynamics spectral element higher order mpi parallel les rans", + "license": "none" + }, + + { + "name": "cp2k", + "description": "quantum chemistry and solid state physics software package that can perform atomistic simulations", + "github": "cp2k/cp2k", + "url": "", + "categories": "scientific", + "tags": "quantum chemistry physics molecular dynamics metadynamics mpi cuda", + "license": "GNU GPL V2" + }, + + { + "name": "Castro", + "description": "An adaptive mesh, astrophysical radiation hydrodynamics simulation code", + "github": "AMReX-Astro/Castro", + "url": "", + "categories": "scientific", + "tags": "adaptive mesh astrophysics radiation hydrodynamics", + "license": "BSD 3-Clause" + }, + + { + "name": "QUIP", + "description": "The QUIP package is a collection of software tools to carry out molecular dynamics simulations.", + "github": "libAtoms/QUIP", + "url": "", + "categories": "scientific", + "tags": "electronic structure calculations quantum chemistry physics molecular dynamics mpi qm-mm", + "license": "GNU GPL V2" + }, + + { + "name": "ABINIT", + "description": "ABINIT is a software suite to calculate the optical, mechanical, vibrational, and other observable properties of materials", + "github": "abinit/abinit", + "url": "", + "categories": "scientific", + "tags": "electronic structure calculations quantum chemistry physics molecular dynamics mpi", + "license": "" + }, + + { + "name": "NASTRAN 95", + "description": "NASA Structural Analysis System, a finite element analysis program (FEA) completed in the early 1970's", + "github": "nasa/NASTRAN-95", + "url": "", + "categories": "scientific", + "tags": "finite element structural eigne stability loads", + "license": "none" + }, + + { + "name": "OFF", + "description": "Finite volume fluid dynamics", + "github": "szaghi/OFF", + "url": "", + "categories": "scientific", + "tags": "godunov riemann euler runge kutta structured", + "license": "GNU GPL v3" + }, + + { + "name": "freeCappuccino", + "description": "A three-dimensional unstructured finite volume code for fluid flow simulations.", + "github": "nikola-m/freeCappuccino", + "url": "", + "categories": "scientific", + "tags": "finite volume turbulent turbulence", + "license": "GNU GPL v3" + }, + + { + "name": "CaNS", + "description": "A code for fast, massively-parallel direct numerical simulations (DNS) of canonical flows", + "github": "p-costa/CaNS", + "url": "", + "categories": "scientific", + "tags": "fluid dynamics fluid simulation computational fluid dynamics turbulence high performance computing hpc cfd", + "license": "" + }, + + { + "name": "Truchas", + "description": "3D Multiphysics Simulation of Metal Casting and Processing", + "github": "truchas/truchas-release", + "url": "", + "categories": "scientific", + "tags": "fluid dynamics metal casting multiphysics hpc", + "license": "BSD 3-Clause" + }, + + { + "name": "dftatom", + "description": "Routines for Radial Integration of Dirac, Schrödinger, and Poisson Equations", + "github": "certik/dftatom", + "url": "", + "categories": "scientific", + "tags": "electronic structure calculations atomic", + "license": "MIT" + }, + + { + "name": "MESA", + "description": "Modules for Experiments in Stellar Astrophysics", + "github": "", + "url": "http://mesa.sourceforge.net/", + "categories": "scientific", + "tags": "stellar astrophysics", + "license": "GNU GPL V2" + }, + + { + "name": "Fortran 2018 examples", + "description": "Easy examples of scientific computing with modern, powerful, easy Fortran 2018 standard", + "github": "scivision/fortran2018-examples", + "url": "", + "categories": "examples", + "tags": "block coarray contiguous mpi namelist openmp random submodule iso_fortran_env", + "license": "GNU GPL V2" + }, + + { + "name": "Fortran patterns", + "description": "Popular design patterns implemented in Fortran", + "github": "farhanjk/FortranPatterns", + "url": "", + "categories": "examples", + "tags": "", + "license": "" + }, + + { + "name": "Numerical methods in fortran", + "description": "Solving linear, nonlinear equations, ordinary differential equations", + "github": "planelles20/numerical-methods-fortran", + "url": "", + "categories": "examples numerical", + "tags": "ode pde integral stochastic quadrature plotting", + "license": "" + }, + + ] \ No newline at end of file diff --git a/_site/packages/projects_search.js b/_site/packages/projects_search.js new file mode 100644 index 000000000..bfcddfe02 --- /dev/null +++ b/_site/packages/projects_search.js @@ -0,0 +1,154 @@ +function findGetParameter(parameterName) { + // Return a GET HTTP parameter + var result = null, + tmp = []; + location.search + .substr(1) + .split("&") + .forEach(function (item) { + tmp = item.split("="); + if (tmp[0] === parameterName) result = decodeURIComponent(tmp[1]); + }); + return result; +} + +function getSubSentences(sentence) { + // Return all permutations of contiguous sub sentences from a sentence + var words = sentence.split(" "); + + var subs = []; + + var N = words.length; + + var i; + for (i = 1; i <= N; i++){ // Loop over possible sentence lengths + + var j; + for (j=0; j<=(N-i); j++){ // Loop over sentence locations + + sub_i = words.slice(j,j+i); + subs.push(sub_i.join(" ")); + + } + + } + + return subs; + +} + +function searchProjects(queryString,projects) { + // Basic sub-string matching within project fields + // + // Results ranked by size of matched sub-string and field weight + // + var subs = getSubSentences(queryString); + + // Sort by subsentence length descending + subs = subs.sort(function(a,b){return b.split(" ").length - a.split(" ").length}) + + var fields = ['name','description','tags','license','github','url']; + var fieldWeights = [10.0,1.0,1.0,0.1,1.0,0.1]; + + // Loop over projects JSON + var i; + for (i = 0; i 0){ + + project = results[i]; + + if (results[i].github != ""){ + out += '

    '; + out += ' '+project.name+'

    '; + } else { + out += '

    '; + if (project.url.includes('gitlab.com')) { + out += ' '; + } else if (project.url.includes('bitbucket.org')){ + out += ' '; + } + out += project.name+'

    '; + } + + out += '

    '+project.description; + + var cats = project.categories.split(" "); + out += ' (' + var j; + for (j=0;j'+cats[j]+''; + if (j'; + + } + + } + + return out; + +} + +// Perform search here onload +var queryString = findGetParameter('query').replace(/\+/g," ").replace(/"/g,''); +document.getElementById('search-query').value = queryString; + +results = searchProjects(queryString,projects); +resultsHTML = resultsToHTML(results); +document.getElementById('search-results').innerHTML = resultsHTML; \ No newline at end of file diff --git a/_site/packages/scientific.html b/_site/packages/scientific.html new file mode 100644 index 000000000..c92ef4b69 --- /dev/null +++ b/_site/packages/scientific.html @@ -0,0 +1,602 @@ + + + + + + + + Scientific Codes - Fortran Programming Language + + + + + + + + + + + + + +

    + + +
    +

    Featured Open Source Projects

    +

    A rich ecosystem of high-performance code

    +
    + +
    +
    +
    + +

    Packages / + + + + Scientific Codes

    +

    + Applications and libraries for applied mathematical and scientific problems +

    + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + +

    + + WRF

    + + + + + +
    + Weather Research and Forecasting model +
    + Tags: +

    + + fds

    + + + +
    + Large-eddy simulation code for low-speed flows, with an emphasis on smoke and heat transport from fires. +
    + Tags: +

    + + Quantum ESPRESSO

    + + + +
    + Quantum ESPRESSO is an integrated suite of Open-Source computer codes for electronic-structure calculations and materials modeling at the nanoscale +
    + Tags: electronic structure calculations quantum chemistry physics molecular dynamics mpi +

    + + fluidity

    + + + +
    + Computational fluid dynamics code with adaptive unstructured mesh capabilities +
    + Tags: cfd computational fluid dynamics unstructured +

    + + Nek5000

    + + + +
    + MPI parallel higher-order spectral element CFD solver +
    + Tags: cfd computational fluid dynamics spectral element higher order mpi parallel les rans +

    + + cp2k

    + + + + + +
    + quantum chemistry and solid state physics software package that can perform atomistic simulations +
    + Tags: quantum chemistry physics molecular dynamics metadynamics mpi cuda +

    + + Castro

    + + + + + +
    + An adaptive mesh, astrophysical radiation hydrodynamics simulation code +
    + Tags: adaptive mesh astrophysics radiation hydrodynamics +

    + + QUIP

    + + + + + +
    + The QUIP package is a collection of software tools to carry out molecular dynamics simulations. +
    + Tags: electronic structure calculations quantum chemistry physics molecular dynamics mpi qm-mm +

    + + ABINIT

    + + + +
    + ABINIT is a software suite to calculate the optical, mechanical, vibrational, and other observable properties of materials +
    + Tags: electronic structure calculations quantum chemistry physics molecular dynamics mpi +

    + + NASTRAN 95

    + + + +
    + NASA Structural Analysis System, a finite element analysis program (FEA) completed in the early 1970's +
    + Tags: finite element structural eigne stability loads +

    + + OFF

    + + + + + +
    + Finite volume fluid dynamics +
    + Tags: godunov riemann euler runge kutta structured +

    + + freeCappuccino

    + + + + + +
    + A three-dimensional unstructured finite volume code for fluid flow simulations. +
    + Tags: finite volume turbulent turbulence +

    + + CaNS

    + + + +
    + A code for fast, massively-parallel direct numerical simulations (DNS) of canonical flows +
    + Tags: fluid dynamics fluid simulation computational fluid dynamics turbulence high performance computing hpc cfd +

    + + Truchas

    + + + + + +
    + 3D Multiphysics Simulation of Metal Casting and Processing +
    + Tags: fluid dynamics metal casting multiphysics hpc +

    + + dftatom

    + + + + + + + +
    + Routines for Radial Integration of Dirac, Schrödinger, and Poisson Equations +
    + Tags: electronic structure calculations atomic +

    + + + MESA

    + + + + + +
    + Modules for Experiments in Stellar Astrophysics +
    + Tags: stellar astrophysics +
    + +
    + +
    +
    + +
    +
    +
    + + + See + + here for how to get your project listed. + +
    +
    + + + + + + + + + + + + + diff --git a/_site/packages/search/index.html b/_site/packages/search/index.html new file mode 100644 index 000000000..32b7a8016 --- /dev/null +++ b/_site/packages/search/index.html @@ -0,0 +1,174 @@ + + + + + + + + Search - Fortran Programming Language + + + + + + + + + + + + + + + + + + + +
    +
    +
    + +

    Packages / Search

    + +
    + + +
    +
    + +
    + +
    + +
    +
    + +
    +
    +
    + + + See + + here for how to get your project listed. + +
    +
    + + + + + + + + + + + + + + diff --git a/_site/packages/strings.html b/_site/packages/strings.html new file mode 100644 index 000000000..04f3c13bc --- /dev/null +++ b/_site/packages/strings.html @@ -0,0 +1,312 @@ + + + + + + + + Characters and strings - Fortran Programming Language + + + + + + + + + + + + + + + + +
    +

    Featured Open Source Projects

    +

    A rich ecosystem of high-performance code

    +
    + +
    +
    +
    + +

    Packages / + + + + Characters and strings

    +

    + Libraries for manipulating characters and strings +

    + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + +

    + + coretran

    + + + +
    + Core fortran routines and object-oriented classes for sorting, kD-Trees, and other algorithms to handle scientific data and concepts +
    + Tags: dynamic array formatting debugging errors kdtree sorting random binary search strings unit testing timing +

    + + StringiFor

    + + + +
    + Fortran strings manipulator +
    + Tags: split join basename search concat +

    + + M_strings

    + + + +
    + Fortran string manipulations +
    + Tags: upper lower quoted join replace white space string conversion tokens split +

    + + + + + Strings for Fortran

    + + + +
    + A library of string functions for Fortran. +
    + Tags: +

    + + + + + iso_varying_string

    + + + +
    + Implementation of the Fortran ISO_VARYING_STRING module in accordance with the standard +
    + Tags: varying length character strings +
    + +
    + +
    +
    + +
    +
    +
    + + + See + + here for how to get your project listed. + +
    +
    + + + + + + + + + + + + + From 686db8e48e79e33692672550495952f5786f8158 Mon Sep 17 00:00:00 2001 From: smeskos Date: Fri, 5 Jun 2020 19:44:48 +0300 Subject: [PATCH 7/8] Update news.xml --- _site/news.xml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/_site/news.xml b/_site/news.xml index d3e79d233..a29a6b081 100644 --- a/_site/news.xml +++ b/_site/news.xml @@ -4,7 +4,7 @@ Fortran Newsletter - 2020-06-05T19:41:32+03:00 + 2020-06-05T19:43:29+03:00 /news From b8de2ad927b16c1a5dc8cbda33006715589a45b8 Mon Sep 17 00:00:00 2001 From: smeskos Date: Fri, 5 Jun 2020 21:42:04 +0300 Subject: [PATCH 8/8] reverted remove of .gitignore --- .gitignore | 1 + _site/CONTRIBUTING.md | 136 --- _site/MINIBOOKS.md | 317 ------ _site/PACKAGES.md | 151 --- _site/assets/css/main.css | 440 -------- _site/assets/css/syntax.css | 73 -- _site/assets/img/discourse.png | Bin 9544 -> 0 bytes _site/assets/img/fortran-logo.svg | 98 -- _site/assets/img/fortran_logo_128x128.png | Bin 2977 -> 0 bytes _site/assets/img/fortran_logo_256x256.png | Bin 5990 -> 0 bytes _site/assets/img/fortran_logo_512x512.png | Bin 12591 -> 0 bytes _site/assets/img/fortran_logo_64x64.png | Bin 1563 -> 0 bytes _site/assets/img/fortran_logo_grey.png | Bin 19657 -> 0 bytes _site/assets/img/fortran_logo_purple_orig.png | Bin 234956 -> 0 bytes _site/assets/img/icons/icon-menu.svg | 13 - _site/assets/js/page_nav.js | 35 - _site/compilers/index.html | 411 -------- _site/favicon.ico | Bin 16958 -> 0 bytes _site/index.html | 353 ------- _site/learn/best_practices.html | 244 ----- _site/learn/index.html | 331 ------ _site/learn/quickstart.html | 469 --------- _site/learn/quickstart/arrays_strings.html | 631 ------------ _site/learn/quickstart/derived_types.html | 804 --------------- _site/learn/quickstart/hello_world.html | 543 ---------- .../quickstart/operators_control_flow.html | 670 ------------ _site/learn/quickstart/organising_code.html | 671 ------------ _site/learn/quickstart/variables.html | 708 ------------- _site/news/archive/index.html | 188 ---- _site/news/index.html | 741 -------------- .../2020/02/28/J3-february-meeting/index.html | 251 ----- .../06/Announcing-FortranCon-2020/index.html | 182 ---- .../2020/04/18/Fortran-Webinar/index.html | 178 ---- .../01/Fortran-Newsletter-May-2020/index.html | 295 ------ .../Fortran-Newsletter-June-2020/index.html | 300 ------ _site/packages/data-types.html | 436 -------- _site/packages/examples.html | 283 ------ _site/packages/graphics.html | 385 ------- _site/packages/index.html | 566 ----------- _site/packages/interfaces.html | 620 ------------ _site/packages/io.html | 589 ----------- _site/packages/libraries.html | 406 -------- _site/packages/numerical.html | 721 ------------- _site/packages/preview.html | 204 ---- _site/packages/programming.html | 370 ------- _site/packages/projects_json.js | 953 ------------------ _site/packages/projects_search.js | 154 --- _site/packages/scientific.html | 602 ----------- _site/packages/search/index.html | 174 ---- _site/packages/strings.html | 312 ------ 50 files changed, 1 insertion(+), 16008 deletions(-) create mode 100644 .gitignore delete mode 100644 _site/CONTRIBUTING.md delete mode 100644 _site/MINIBOOKS.md delete mode 100644 _site/PACKAGES.md delete mode 100644 _site/assets/css/main.css delete mode 100644 _site/assets/css/syntax.css delete mode 100644 _site/assets/img/discourse.png delete mode 100644 _site/assets/img/fortran-logo.svg delete mode 100644 _site/assets/img/fortran_logo_128x128.png delete mode 100644 _site/assets/img/fortran_logo_256x256.png delete mode 100644 _site/assets/img/fortran_logo_512x512.png delete mode 100644 _site/assets/img/fortran_logo_64x64.png delete mode 100644 _site/assets/img/fortran_logo_grey.png delete mode 100644 _site/assets/img/fortran_logo_purple_orig.png delete mode 100644 _site/assets/img/icons/icon-menu.svg delete mode 100644 _site/assets/js/page_nav.js delete mode 100644 _site/compilers/index.html delete mode 100644 _site/favicon.ico delete mode 100644 _site/index.html delete mode 100644 _site/learn/best_practices.html delete mode 100644 _site/learn/index.html delete mode 100644 _site/learn/quickstart.html delete mode 100644 _site/learn/quickstart/arrays_strings.html delete mode 100644 _site/learn/quickstart/derived_types.html delete mode 100644 _site/learn/quickstart/hello_world.html delete mode 100644 _site/learn/quickstart/operators_control_flow.html delete mode 100644 _site/learn/quickstart/organising_code.html delete mode 100644 _site/learn/quickstart/variables.html delete mode 100644 _site/news/archive/index.html delete mode 100644 _site/news/index.html delete mode 100644 _site/newsletter/2020/02/28/J3-february-meeting/index.html delete mode 100644 _site/newsletter/2020/04/06/Announcing-FortranCon-2020/index.html delete mode 100644 _site/newsletter/2020/04/18/Fortran-Webinar/index.html delete mode 100644 _site/newsletter/2020/05/01/Fortran-Newsletter-May-2020/index.html delete mode 100644 _site/newsletter/2020/06/01/Fortran-Newsletter-June-2020/index.html delete mode 100644 _site/packages/data-types.html delete mode 100644 _site/packages/examples.html delete mode 100644 _site/packages/graphics.html delete mode 100644 _site/packages/index.html delete mode 100644 _site/packages/interfaces.html delete mode 100644 _site/packages/io.html delete mode 100644 _site/packages/libraries.html delete mode 100644 _site/packages/numerical.html delete mode 100644 _site/packages/preview.html delete mode 100644 _site/packages/programming.html delete mode 100644 _site/packages/projects_json.js delete mode 100644 _site/packages/projects_search.js delete mode 100644 _site/packages/scientific.html delete mode 100644 _site/packages/search/index.html delete mode 100644 _site/packages/strings.html diff --git a/.gitignore b/.gitignore new file mode 100644 index 000000000..c08f9add7 --- /dev/null +++ b/.gitignore @@ -0,0 +1 @@ +_site \ No newline at end of file diff --git a/_site/CONTRIBUTING.md b/_site/CONTRIBUTING.md deleted file mode 100644 index 022284e51..000000000 --- a/_site/CONTRIBUTING.md +++ /dev/null @@ -1,136 +0,0 @@ -# Contributing to fortran-lang.github.io - -Fortran-lang.github.io is open-source and contributions are welcome! -The Fortran-lang site uses the Ruby-based [Jekyll static site generator](https://jekyllrb.com/). -To contribute you will therefore need to install Jekyll on your development computer. -See [README.md](README.md) for how to setup Jekyll and build the site. - -* See [PACKAGES](./PACKAGES.md) for how to add an entry to the [Package index](https://fortran-lang.org/packages) - -* See [MINIBOOKS](./MINIBOOKS.md) for how to write and structure a mini-book tutorial for the [Learn](https://fortran-lang.org/learn) section - -## Workflow - -Contributions to the site are made by pull request to the github repository: . - -The workflow for doing so takes the following form: - -1. Create/update a personal fork of fortran-lang.github.io - - (See [github help: syncing a fork](https://help.github.com/en/github/collaborating-with-issues-and-pull-requests/syncing-a-fork) ) - -2. Create a new branch in your fork - - The branch name should concisely describe your contribution, _e.g._ `fix-spelling-homepage`, `update-compiler-info` - -3. Perform your changes on the local branch - -4. Push your modified branch to your local fork - - _e.g._ `git push --set-upstream origin fix-spelling-homepage` - -5. Create a pull request in the fortran-lang/fortran-lang.github.io from your modified fork branch - - (See [github help: creating a pull request](https://help.github.com/en/github/collaborating-with-issues-and-pull-requests/creating-a-pull-request) ) - -__Note: Before opening a pull request you must build your changes locally using Jekyll (see [README.md](README.md)) to verify that your changes build correctly and render as you expect.__ - -Your pull request will be reviewed by other members of the community who may request changes. - -__Note: You can continue to push changes to your fork branch after you open a pull request - the pull request will update accordingly__ - -Once your pull request is approved, usually by at least two other community members, it will be merged into the fortran-lang.github.io master branch by the maintainers at which point it will be published to the fortran-lang.org site. - -If required, the repository maintainers can build a public preview of your proposed changes which will be available to view at `fortran-lang.org/pr//` where `` is the numeric identifier of your pull request. - -This allows reviewers to directly view the generated result of your PR. -After a pull request has been merged and successfully rendered, the maintainers will delete the preview build. - - -## Style guide - -### External links - -It is recommended practice for off-site hyperlinks to open in a new tab. -On `Fortran-lang.org` all such links will automatically be suffixed with a new-tab icon; -this gives site users prior expectation that the link will lead them off-site while -keeping fortran-lang.org open in a previous tab. - -__Example:__ Open link in new tab (HTML or markdown) -```html -Discourse -``` - -### Internal site links - -Hyperlinks that point to other parts of the fortran-lang.org website should be prefixed with `{{ site.baseurl }}` - this is important for generating pull request previews (see [here](https://byparker.com/blog/2014/clearing-up-confusion-around-baseurl/) for an explanation). - -__Example:__ markdown link - -``` -[Fortran-lang news]({{site.baseurl}}/News) -``` - -__Example:__ html link - -``` -Fortran packages -``` - -### Icon packs - -Icons are an easy way to improve page aesthetic by breaking-up otherwise monotonic text passages -and drawing attention to headings or key information. - -Three icon packs are available for use on `fortran-lang.org`: - -* [Font awesome](https://fontawesome.com/icons?d=gallery) (CC BY 4.0 License) - -* [Feather](https://feathericons.com/) (MIT) - -* [Devicon](https://konpa.github.io/devicon/) (MIT) - - -__Example:__ Font awesome -```html - -``` - -__Example:__ Feather - -```html - -``` - -__Example:__ Devicon - -```html - -``` - -Visit the respective websites to browse available icons. - -__Note:__ font-awesome icons currently appear to vertically-align with text better - -we need to get feather icons to do the same. - - -### Page contents - -It is sometimes useful to display a hyperlinked page contents for lengthy pages. -There are two ways to do this on `fortran-lang.org`. - -__Option 1: Use the `book` layout__ - -The `book` layout is the layout used for mini-book tutorials; -it includes a non-scrolling sidebar which is automatically populated -by the `

    ` headings on the current page. - -__Option 2:__ - -If you just want a list of headings at the top of your page, -include the following snippet, which will be automatically -populated by the `

    ` headings on the current page. - -```html - -``` - -__Implementation:__ -the functionality described above is implemented in the javascript file -[assets/js/page_nav.js](./assets/js/page_nav.js). diff --git a/_site/MINIBOOKS.md b/_site/MINIBOOKS.md deleted file mode 100644 index c4fd9b88a..000000000 --- a/_site/MINIBOOKS.md +++ /dev/null @@ -1,317 +0,0 @@ -# Mini-book Tutorials on fortran-lang.org - -This guide will cover how to write mini-book tutorials for the [Learn](https://fortran-lang.org/learn) -section of . - -See [CONTRIBUTING](./CONTRIBUTING.md) for general guidance on contributing to . - -## 0. Mini-book formats - -Mini-books are designed to be mostly self-contained tutorials on a particular feature -of the Fortran language. - -There are two types of mini-book format: - -* __Single-page:__ all content is written within a single markdown file and displayed -on a single webpage; - -* __Multi-page:__ tutorial content is written across multiple markdown files and displayed -as a collection of webpages. - - -The choice of book type depends on the length of your content and how you intend to structure it. - -Consider the table of contents that will be produced: - -* Single-page books have __one level__ of navigation: a link for each `

    ` heading in the tutorial - -* Multi-page books have __two levels__ of navigation: a link for each page, and a link for each `

    ` heading on the current page - -Single-page mini-books are simpler to produce and should be used for brief topics or short tutorials that will -eventually be subsumed into a more-comprehensive multi-page book. - -Multi-page books are recommended for more-comprehensive tutorials that can be structured with one subtopic per page. - -The rest of this guide is split into two sections, one each for the single-page and multi-page book types. - -## 1. Single-page mini-book - -The steps required for publishing a single-page mini-book are: - -* Create a new markdown document in the `./learn` directory - -* Write your tutorial content - -* Add an entry to [_data/learning.yml](./_data/learning.yml) for your new mini-book - -* Open a pull request - -### 1.1 Writing your mini-book in markdown - -For single-page mini-books your tutorial will be entirely contained within a single markdown document. - -First create a new markdown document in the `./learn/` directory with the `.md` file extension -and a short name that concisely describes the topic of your tutorial, _e.g._ `./learn/file_io.md`. - -Open your new markdown file and add a header in the following format: - -``` ---- -layout: book -title: -permalink: /learn/ ---- -``` - -You should replace `` with a human-readable description of your tutorial content; -this will be displayed as an `

    ` heading at the top of your mini-book page. - -Replace `` with the filename of your markdown file -but __excluding the `.md` extension__. There should also be no trailing slash. - - -__Example:__ header - -``` ---- -layout: book -title: Reading and writing files in Fortran -permalink: /learn/file_io ---- -``` - -__NOT:__ `permalink: /learn/file_io.md` - -__NOT:__ `permalink: /learn/file_io/` - -You can now fill the rest of the file with your tutorial content written in markdown; -see [Kramdown syntax](https://kramdown.gettalong.org/syntax.html) for documentation on -the markdown implementation. - - -### 1.2 Structuring your mini-book with headings - -You should use `

    ` headings to break-up your single-page mini-book into a logical -structure. -Each `

    ` heading will show up in the hyperlinked table-of-contents. - -In markdown, `

    ` headings can be written as: - -```markdown - -My heading ----------- - -``` - -__OR__ - -```markdown - -## My heading - -``` - -__OR__ - - -```markdown - -## My heading ## - -``` - -__Note:__ make sure to include a blank line before your heading. - - -### 1.3 Add your mini-book to the Learn page - -To add your new mini-book to the _Learn_ page, you need to add a new entry -in the [_data/learning.yml](./_data/learning.yml) datafile. - -Open this file and create a new entry under the `books:` field in the following format: - -```yaml - - - title: - description: - category: - link: /learn/ - -``` - -The `title` field is what will be displayed on the _Learn_ page for your mini-book -and should generally be the same as the `title` field in your markdown file, but this isn't required. - -The contents of the `description` field is also displayed on the _Learn_ page -and should briefly summarise the contents of your mini-book tutorial. - -The `category` field should match one of the categories listed at the top of the data file (under -the `categories:` field) and is used to group tutorials on the Learn page. - -The `link` field should exactly match the `permalink` field in your markdown document. - -__Example:__ `learning.yml` book entry - -```yaml - - - title: File input and output - description: A tutorial on reading and writing files in Fortran - category: Getting started - link: /learn/file_io - -``` - -Save the modified `learning.yml` data file and rebuild the website on your local machine to check the results. -If successful, a new link should appear on the _Learn_ page with the title of your new mini-book. - -Once you have completed your mini-book and added an entry to the `learning.yml` data file, open a pull request -at (see [CONTRIBUTING](./CONTRIBUTING.md)). - - - -## 2. Multi-page mini-books - -The steps required for publishing a multi-page mini-book are: - -* Create a new folder in the `./learn/` directory - -* Create an `index.md` file in your new folder - -* Write your tutorial content in markdown files in your new folder - -* Add an entry to [_data/learning.yml](./_data/learning.yml) for your new mini-book - -* Open a pull request - - -### 2.1 Create a new folder for your mini-book - -Create a new folder in the `./learn/` directory with a short name that concisely describes the topic of your tutorial, _e.g._ `./learn/coarrays/`. -All pages of your mini-book will be contained within this folder. - -The first page of your mini-book should be called `index.md`, so create a new markdown file in -your mini-book folder called `index.md`, and add a header in the following format: - - -``` ---- -layout: book -title: -permalink: /learn/ ---- -``` - -The `title` field should contain a human-readable description of your mini-book tutorial -and this will be displayed as an `

    ` heading at the top of this first page. - -The `permalink` field should contain `/learn/` followed by the name of your mini-book folder. -__There should be no trailing slash.__ - -__Example:__ header for `index.md` -``` ---- -layout: book -title: Parallel programming with Coarrays -permalink: /learn/coarrays ---- -``` - -__NOT:__ `permalink: /learn/coarrays/` - -In your table of contents, this first page will be displayed as '_Introduction_'; -you should populate the remainder of `index.md` with an introduction to your -mini-book tutorial which may include: a summary of the concepts covered; any prerequisites; and -any references to other related mini-books or useful third-party resources. - -### 2.2 Add pages to your mini-book - -For each new page in your mini-book, create a new markdown file in your mini-book folder. -Each page needs a header, just like the `index.md`, but the `title` and `permalink` fields -must be unique to each new page. - -``` ---- -layout: book -title: -permalink: /learn// ---- - -``` -Replace `` with the title of your new page; this will be displayed as -an `

    ` header at the top of the page and in the hyperlinked table-of-contents. - -Replace `` with the name of the markdown file for your new page -but __excluding the `.md` extension__. - -__Example:__ a header for a new page `./learn/coarrays/background.md` - -``` ---- -layout: book -title: What are coarrays? -permalink: /learn/coarrays/background ---- -``` - -As with single-page mini-books, you should use `

    ` headings to break-up each -page into a logical structure. -Each `

    ` heading on the current page will show up in the hyperlinked table-of-contents. - - - - -### 2.3 Add your mini-book to the Learn page - -To add your new mini-book to the _Learn_ page, you need to add a new entry -in the [_data/learning.yml](./_data/learning.yml) datafile. - -Open this file and create a new entry under the `books:` field in the following format: - -```yaml - - - title: - description: - category: - link: /learn/ - pages: - - link: /learn// - - link: /learn// - - link: /learn// - -``` - -The `title` field is what will be displayed on the _Learn_ page for your mini-book -and should generally be the same as the `title` field in your `index.md` markdown file, but this isn't required. - -The contents of the `description` field is also displayed on the _Learn_ page -and should briefly summarise the contents of your mini-book tutorial. - -The `category` field should match one of the categories listed at the top of the data file (under -the `categories:` field) and is used to group tutorials on the Learn page. - -The top-level `link` field should exactly match the `permalink` field in your `index.md` file. - -Each `link` field under `pages` should exactly match the `permalink` field in each of your subsequent mini-book pages. -Pages are listed in the table-of-contents in the order that they are listed under `pages`. - -__Example:__ `learning.yml` book entry - -```yaml - - - title: Parallel programming with Coarrays - description: A tutorial on parallel programming using coarrays - category: Parallel programming - link: /learn/coarrays - pages: - - link: /learn/coarrays/background - - link: /learn/coarrays/codimension - - link: /learn/coarrays/examples - -``` - -Save the modified `learning.yml` data file and rebuild the website on your local machine to check the results. -If successful, a new link should appear on the _Learn_ page with the title of your new mini-book. - -Once you have completed your mini-book and added an entry to the `learning.yml` data file, open a pull request -at (see [CONTRIBUTING](./CONTRIBUTING.md)). diff --git a/_site/PACKAGES.md b/_site/PACKAGES.md deleted file mode 100644 index 1b1969bd0..000000000 --- a/_site/PACKAGES.md +++ /dev/null @@ -1,151 +0,0 @@ -# Fortran-lang.org package index - - -## Package criteria - -The following criteria are required of packages to be indexed: - -- __Relevance__: the package must be primarily implemented in Fortran or provide -a complete Fortran interface to an existing package or be purposed solely towards -software development in Fortran. - -- __Maturity__: the primary functionality of the package shall be implemented. -No prototype, testing or partially complete packages will be accepted. -If the package is hosted on github or similar, it should have at least 5 'stars'. - -- __Availability__: the package source shall be freely available for browsing online -or cloning or downloading - -- __Open source__: the package shall be licensed under an appropriate [open-source license](https://opensource.org/licenses) -with the license file clearly included with the source code - -- __Uniqueness__: the package shall not be a fork or minor revision of existing packages - -- __README__: the package shall have some form of README or landing-page clearly -stating the package purpose and functionality. This should also contain information -on the package dependencies and the steps required to build and run. - - -The following criteria are not required but are recommended: - -- __Documentation__: any form of written documentation aimed at users of the package. Ideally -this should cover: - - Supported / tested compilers - - Dependencies - - Build and install process - - Modules contained within the package - - Procedures made available and their interfaces - - Example code - -- __Contributing__: details on how users may submit issues and contribute to the development of the -package - -- __Tests__: any form of executable test(s) that can be used to verify the functionality of the package - -- __Portability__: no non-standard language extensions or proprietary dependencies - -- __FPM__: support installation by the Fortran Package Manager [fpm](https://github.com/fortran-lang/fpm) - - -## Process for adding packages - -1. Users should confirm that their project meets the minimum requirements for listing in the -Fortran-lang package index, as written in this document - -2. Users should open a pull request using the 'Package index request' template - -3. At least three Fortran-lang community members shall review the request against the criteria above - -4. If three or more Fortran-lang community members agree that the package should be listed and there is no significant objection, then the pull request will be merged - - -## Package index requests - -Package index requests are made by pull requests against the [fortran-lang.github.io repository](https://github.com/fortran-lang/fortran-lang.github.io/). -See [this guide](https://guides.github.com/activities/forking/) for guidance on forking and making pull requests. - -Package details are listed in the `_data/package_index.yml` data file. - -To add a package simply create a new entry within this file. -The data file is ordered by high-level categories merely to aid in navigation; -find the appropriate category for your package and create a new entry. - -### Github hosted packages - -``` - - name: - github: / - description: - categories: [category2] - tags: [tag1] [tag2] [tag3] - version: [version] - license: [license] -``` - -Valid categories: -- `libraries`: general libraries -- `interfaces`: libraries that provide interfaces to other libraries, software or devices -- `programming`: general programming utilities: errors, logging, testing, documentation _etc._ -- `data-types`: libraries providing advanced data types: containers, datetime, resizable arrays _etc._ -- `strings`: string handling libraries -- `io`: libraries that parse and generate various file formats -- `graphics`: plotting and GUIs -- `numerical`: matrices, linear algebra, solvers, root-finding, interpolation, optimization, differential eqns, statistics, machine learning, random numbers _etc._ -- `scientific`: domain-specific scientific libraries or applications -- `examples`: repositories offering language feature demonstrations, tutorials and benchmarks - -__Projects listing more than one category must provide good justification thereof -in the pull request.__ - -__Notes:__ - -- The package description should clearly describe the functionality of the package in a single sentence. - -- Tags (optional) should contain any terms not already contained in the name or description that users may search directly for. Tags should be separate by spaces. - -- Package version - - this can be determined automatically if a versioned release has been created on github - - if version is specified, it will override any detected github version - - if version is 'none', then no version information will be displayed. (Use this if - your package has no version.) - -- Package license - - this can be determined automatically if github is able to detect a known license - - license must be specified if github is unable to detect a known license - -### Non-github hosted packages - -``` - - name: - url: - description: - categories: [category2] - tags: [tag1] [tag2] [tag3] - version: [version] - license: -``` - -__Notes:__ - -- License and version information cannot be detected automatically for non-github repositories -- if your package has no version, then omit the version field -- a license must be specified for non-github repositories - - -### Member review checklist - -Community members reviewing packages should cover the following points: - -1. Ensure the package meets the minimum criteria as written in this document - -2. Check the package metadata - - Repository exists and is accessible - - Description clearly and concisely describes the package - - Assigned category is appropriate - -3. Check license information - - If license field has been omitted: check that github has detected the license - - If license field is included: check that it matches repository license file - -After merge: - - Check that package is available in expected category and search \ No newline at end of file diff --git a/_site/assets/css/main.css b/_site/assets/css/main.css deleted file mode 100644 index 5e7a317d2..000000000 --- a/_site/assets/css/main.css +++ /dev/null @@ -1,440 +0,0 @@ -* { - -moz-box-sizing: border-box; - box-sizing: border-box; -} - -body { - font-family: 'Helvetica Neue', Helvetica, Arial, sans-serif; - font-size: 15px; - line-height: 1.4; - color: #444; - background-color: #fbfbfb; -} -@media (min-width: 568px) { - body { - font-size: 17px; - } -} - -a { - color: #3c92d1; - text-decoration: none; -} - -.current a { - font-weight: bold; -} - -.button { - background-color: #734f96; - border: none; - color: white; - padding: 10px 32px; - text-align: center; - text-decoration: none; - display: inline-block; - font-size: 20px; - border-radius: 8px; -} - -.button.center { - display: block; - margin: 0 auto; - width: fit-content; -} - -.button:hover { - background-color: #777; - color: white; - text-decoration: none; -} - -.button.blue{ - background-color: #008CBA; -} - -.button.blue:hover{ - background-color: #777; -} - -#page-nav { - padding-left: 20px; -} - -h1, -h2, -h3 { - font-family: 'Lato', sans-serif; -} - -h1 { - color: #734f96; -} - -h2 { - font-size: 24px; - font-weight: 400; - color: #734f96; -} -@media (min-width: 568px) { - h2 { - font-size: 30px; - } -} -h3 { - /* color: #54a23d; */ -} - -/* Mark new-window links */ -a[target="_blank"]:after { - content: url(data:image/png;base64,iVBORw0KGgoAAAANSUhEUgAAAAoAAAAKCAYAAACNMs+9AAAAQElEQVR42qXKwQkAIAxDUUdxtO6/RBQkQZvSi8I/pL4BoGw/XPkh4XigPmsUgh0626AjRsgxHTkUThsG2T/sIlzdTsp52kSS1wAAAABJRU5ErkJggg==); - margin: 0 3px 0 5px; -} - -/* " except in the navbar and buttons*/ -.navbar a[target="_blank"]:after { - content:''; - margin: 0px; -} -.button[target="_blank"]:after { - content:''; - margin: 0px; -} - -/* Hide text for social navbar icons - if not on mobile device*/ -@media (min-width: 758px) { - .navbar .icon-link{ - display: none; - } -} - -blockquote { - border-left: 5px solid #eeeeee; - margin-left: 0; - padding-left: 15px; -} - -blockquote small { - display: block; - font-size: 80%; - line-height: 1.4; -} - -blockquote small:before { - content: '\2014 \00A0' -} - -pre { - overflow: auto; - padding: 0.8rem; - border-radius: 0.2rem; - border: solid 1px rgba(0, 0, 0, 0.1); - background-color: rgba(0, 0, 0, 0.05); - white-space: pre-wrap; -} - -.container { - margin: 0 15px; -} -@media (min-width: 568px) { - .container { - margin: 0 auto; - width: 90%; - max-width: 1200px; - } -} - -.container-flex{ - margin: 0 auto; - width: 90%; - display: flex; - flex-wrap: wrap; -} - -.col-flex { - /* display: table-cell; */ - flex: 45%; - padding-left: 10px; - vertical-align: top; -} - -@media screen and (max-width: 700px) { - .col-flex { - flex: 100%; - flex-direction: column; - } -} - -#navbar-logo { - height: 3em; -} -.navbar-top-align { - margin-top:1em; -} - .col-half { - display: table-cell; - width: 50%; - min-width: 50%; - vertical-align: top; - } - .col-half.second { - padding-left: 6%; - } -.navbar-right .dropdown-menu { - left: 0px; -} - -.masthead { - border-top: solid 1px #ececec; - border-bottom: solid 1px #ececec; - text-align: center; - padding: 20px 12px; -} -@media (min-width: 568px) { - .masthead { - padding-top: 40px; - padding-bottom: 40px; - } -} - -.masthead .container { -} -@media (min-width: 568px) { - .masthead .container { - width: 568px; - margin: 0 auto; - } -} - -.masthead h1 { - font-size: 20px; - font-weight: 400; -} -@media (min-width: 568px) { - .masthead h1 { - font-size: 40px; - margin-bottom: 20px; - } -} - -.masthead .lead { - font-weight: 900; - color: #54a23d; - font-family: 'Lato', sans-serif; - font-size: 16px; - font-weight: 900; -} -@media (min-width: 568px) { - .masthead .lead { - font-size: 26px; - } -} - -.masthead .btn { - margin-top: 0.5em; -} -@media (min-width: 568px) { - .masthead .btn { - font-size: 20px; - } -} - -.col-wide, -.col-narrow { - display: block; -} -@media (min-width: 568px) { - .col-wide { - display: table-cell; - width: 61.8%; - vertical-align: top; - } - .col-narrow { - display: table-cell; - width: 38.2%; - padding-left: 6%; - vertical-align: top; - } -} - -.col-right, -.col-fixed { - display: block; -} - -@media (min-width: 568px) { - .col-right { - /* display: table-cell; */ - width: 61.8%; - vertical-align: top; - margin-left: 380px; - min-height: 500px; - } - .col-fixed { - /* display: table-cell; */ - position: fixed; - width: 350px; - height: 500px; - z-index: 1; /* Stay on top */ - } - .col-fixed .content{ - overflow-y: auto; - overflow-x: hidden; - height: 90%; - width: 100%; - } -} - - -.front-section { - padding: 8px 0; -} -@media (min-width: 568px) { - .front-section { - padding-top: 30px; - padding-bottom: 30px; - display: table; - width: 100%; - } - .front-section h2:first-child { - margin-top: 0; - } -} - -.front-section.shaded { - background-color: #f4f4f4; -} - -.front-section.shaded.purple { - background-color: #f2eef6; -} - - -.faqs dt { - font-weight: 700; -} - -.faqs dd { - color: #777; - font-size: 15px; - margin-left: 0; - margin-bottom: 20px; -} - -.faqs dd pre { - font-size: 0.9rem; -} - -.btn { - display: inline-block; - text-align: center; - vertical-align: middle; - background-color: #3c92d1; - color: #fff; - font-family: 'Lato', sans-serif; - border-radius: 4px; - padding: 15px 30px; -} - -.btn:hover { - background-color: #3889c4; - color: white; -} - -.btn.full-width { - width: 100%; -} - -.search-btn { - display: inline-block; - text-align: center; - vertical-align: middle; - background-color: #3c92d1; - color: #fff; - font-family: 'Lato', sans-serif; - border-radius: 4px; - padding: 5px 7px; -} - -.search-btn:hover { - background-color: #3889c4; - color: white; -} - -.search-box { - width: 85%; - padding: 5px 7px; - color: #777; - font-weight: bold; -} - - -footer .container { - border-top: solid 1px #ececec; - padding: 20px 0 50px; - font-size: 12px; - color: #777; -} - -footer .col-narrow { - text-align: right; -} - -@media (min-width: 568px) { - footer .container { - font-size: 14px; - display: table; - } -} - -footer a { - color: #444; -} - - -.light { - color: #777; -} - -.light a { - color: #444; -} - -.small { - font-size: 70%; -} - -.newsletter h1 { - margin-bottom: 0px; -} - -.aside-note { - color: gray; - /* border-left: 5px solid #734f96; */ - border-left: 5px solid gray; - font-size: 16px; - padding-left: 10px; - margin: 20px 0; -} - -.aside-tip { - border-left: 5px solid #3c92d1; - font-size: 16px; - padding-left: 10px; - margin: 20px 0; -} - -.aside-important { - border-left: 5px solid #c7254e; - font-size: 16px; - padding-left: 10px; - margin: 20px 0; - background-color: #f9f2f4; -} - -.projects-table td{ - - padding: 4px; - -} \ No newline at end of file diff --git a/_site/assets/css/syntax.css b/_site/assets/css/syntax.css deleted file mode 100644 index b3806e885..000000000 --- a/_site/assets/css/syntax.css +++ /dev/null @@ -1,73 +0,0 @@ -/* - friendly.css - source: https://github.com/richleland/pygments-css (Unlicense/PD) -*/ -.highlight .hll { background-color: #ffffcc } -.highlight { background: #f0f0f0; } -.highlight .c { color: #60a0b0; font-style: italic } /* Comment */ -.highlight .err { border: 1px solid #FF0000 } /* Error */ -.highlight .k { color: #007020; font-weight: bold } /* Keyword */ -.highlight .o { color: #666666 } /* Operator */ -.highlight .ch { color: #60a0b0; font-style: italic } /* Comment.Hashbang */ -.highlight .cm { color: #60a0b0; font-style: italic } /* Comment.Multiline */ -.highlight .cp { color: #007020 } /* Comment.Preproc */ -.highlight .cpf { color: #60a0b0; font-style: italic } /* Comment.PreprocFile */ -.highlight .c1 { color: #60a0b0; font-style: italic } /* Comment.Single */ -.highlight .cs { color: #60a0b0; background-color: #fff0f0 } /* Comment.Special */ -.highlight .gd { color: #A00000 } /* Generic.Deleted */ -.highlight .ge { font-style: italic } /* Generic.Emph */ -.highlight .gr { color: #FF0000 } /* Generic.Error */ -.highlight .gh { color: #000080; font-weight: bold } /* Generic.Heading */ -.highlight .gi { color: #00A000 } /* Generic.Inserted */ -.highlight .go { color: #888888 } /* Generic.Output */ -.highlight .gp { color: #c65d09; font-weight: bold } /* Generic.Prompt */ -.highlight .gs { font-weight: bold } /* Generic.Strong */ -.highlight .gu { color: #800080; font-weight: bold } /* Generic.Subheading */ -.highlight .gt { color: #0044DD } /* Generic.Traceback */ -.highlight .kc { color: #007020; font-weight: bold } /* Keyword.Constant */ -.highlight .kd { color: #007020; font-weight: bold } /* Keyword.Declaration */ -.highlight .kn { color: #007020; font-weight: bold } /* Keyword.Namespace */ -.highlight .kp { color: #007020 } /* Keyword.Pseudo */ -.highlight .kr { color: #007020; font-weight: bold } /* Keyword.Reserved */ -.highlight .kt { color: #902000 } /* Keyword.Type */ -.highlight .m { color: #40a070 } /* Literal.Number */ -.highlight .s { color: #4070a0 } /* Literal.String */ -.highlight .na { color: #4070a0 } /* Name.Attribute */ -.highlight .nb { color: #007020 } /* Name.Builtin */ -.highlight .nc { color: #0e84b5; font-weight: bold } /* Name.Class */ -.highlight .no { color: #60add5 } /* Name.Constant */ -.highlight .nd { color: #555555; font-weight: bold } /* Name.Decorator */ -.highlight .ni { color: #d55537; font-weight: bold } /* Name.Entity */ -.highlight .ne { color: #007020 } /* Name.Exception */ -.highlight .nf { color: #06287e } /* Name.Function */ -.highlight .nl { color: #002070; font-weight: bold } /* Name.Label */ -.highlight .nn { color: #0e84b5; font-weight: bold } /* Name.Namespace */ -.highlight .nt { color: #062873; font-weight: bold } /* Name.Tag */ -.highlight .nv { color: #bb60d5 } /* Name.Variable */ -.highlight .ow { color: #007020; font-weight: bold } /* Operator.Word */ -.highlight .w { color: #bbbbbb } /* Text.Whitespace */ -.highlight .mb { color: #40a070 } /* Literal.Number.Bin */ -.highlight .mf { color: #40a070 } /* Literal.Number.Float */ -.highlight .mh { color: #40a070 } /* Literal.Number.Hex */ -.highlight .mi { color: #40a070 } /* Literal.Number.Integer */ -.highlight .mo { color: #40a070 } /* Literal.Number.Oct */ -.highlight .sa { color: #4070a0 } /* Literal.String.Affix */ -.highlight .sb { color: #4070a0 } /* Literal.String.Backtick */ -.highlight .sc { color: #4070a0 } /* Literal.String.Char */ -.highlight .dl { color: #4070a0 } /* Literal.String.Delimiter */ -.highlight .sd { color: #4070a0; font-style: italic } /* Literal.String.Doc */ -.highlight .s2 { color: #4070a0 } /* Literal.String.Double */ -.highlight .se { color: #4070a0; font-weight: bold } /* Literal.String.Escape */ -.highlight .sh { color: #4070a0 } /* Literal.String.Heredoc */ -.highlight .si { color: #70a0d0; font-style: italic } /* Literal.String.Interpol */ -.highlight .sx { color: #c65d09 } /* Literal.String.Other */ -.highlight .sr { color: #235388 } /* Literal.String.Regex */ -.highlight .s1 { color: #4070a0 } /* Literal.String.Single */ -.highlight .ss { color: #517918 } /* Literal.String.Symbol */ -.highlight .bp { color: #007020 } /* Name.Builtin.Pseudo */ -.highlight .fm { color: #06287e } /* Name.Function.Magic */ -.highlight .vc { color: #bb60d5 } /* Name.Variable.Class */ -.highlight .vg { color: #bb60d5 } /* Name.Variable.Global */ -.highlight .vi { color: #bb60d5 } /* Name.Variable.Instance */ -.highlight .vm { color: #bb60d5 } /* Name.Variable.Magic */ -.highlight .il { color: #40a070 } /* Literal.Number.Integer.Long */ \ No newline at end of file diff --git a/_site/assets/img/discourse.png b/_site/assets/img/discourse.png deleted file mode 100644 index 599f68a711f8cef40b063398f4e2793d1561f48d..0000000000000000000000000000000000000000 GIT binary patch literal 0 HcmV?d00001 literal 9544 zcmZ{~Wl&tt6E3{?;)}a17CcyRcS3N7;O_3a!9#Es2pU2H1PD&hzy=BKvbYlnS=<(X z`TcLbAMS^HPSwox%sk!GQ)i@3KZ)9!D)>0mH~;_uUrkj}7XUzkJeQq-n9nJN{hOud z4Bb&qLk<9_PsP2r#(0()ZB=zO0DurS03a#`0JwdwirNPN{P_TY11kVPJog#tRnV>@ z`P_hMqpqR|c>3@C^s_t@0AR6HQTQq`1~THS*F~MORk43 z#N?81prNwOf>cql!Li!%@{F=LY1+g~Sm0RFnJ&_hV=FY_R=^MM7VgFDY75Qwj)%uw z9qvNSz{Zx)@=T%by~P2qrNaN7z(0j8lot%jD49`-XY1Iq*lEnEVZnX?4Ouj8LLpQG zm?NzGZ2eM}i#l0ZaFAc1$%5BP`~)MImIEuOJV6z5LVO}{l1EDZ++6yXISiHqv6scS zDm&c=tf6)hW*r!nOgRbtwI%m@Q718m7U`)13?dRmJ2`-tKG%nsXA$TN}dkz*@q}1?;=%_|b%P%RUZlw2%llcR+4a(KMs3*B3wCtA>3zg52mP>G%}M9-K(8lcgM1orJdZ_76Rq1#p-}g zQ|6kbQx}e4KGGnH^f@lptl-XqT%$qkV2lr!;*Rc%)QKmi>ddJkvuD<>zLrgwBrqco zw)^u`maSu>P@Hgkxp8s|tnKZ&#wwU(n4MUXrQ%r6d>KlZ+!O|e{&H;v#xu7vVLqm* z@z&78-JA)};@e${JgQ&Fn;Kz>pu+!olutR`mV#PQkl$v=*iVCy7T#0?yW}j@Z{nSG zbKKL+4@#;R7}uBM;H&i4;)1B|%Dm0)(pUQN*hWA2Sy<3}vr`zmYZrUf$MFBU90O03 zHpo^lg{UiQ;4clb!kRNRo+UI9*M)xd=?DHi>q zh*AO7CqK^~8wdD=P*I*zCASdTTN|Hjm#|C{sx7P`NfJhDyp&+go{~;4ak_@q2ZptL44d0Z(EV zrX)h!q#TWK@Rv;9;o0%=zoVKdr)nI?c9dg5`(nllss}e6q&6pc{XjnRqaIVMbE;+9 zNNni6Q|CS%8R2KI}vbiStxOz!8|D&!# zkra&O)3}3JIZ7&PP>u$SDB)!7zh%vW-azE?$y;;9$@v$khSpS*`!JH(de{+z{d8dc zlRuQOH*i+6)7Q~vM=W=Ql@{D|OR}{7R@3P)}6C{Ve3%NIZj)NpW{VDEJY6%J|TB_H=ryO-0ldK7a13@Ax@HDN^SQ(jTgmx?gW(v9`W`KQqm!93Wiu zSMOxJIJ&$cqt>pu&Q=lI6@IMIfA|&%oh;7ie8jQJi#-=X^W68SopK_^h7_ZyEb`m~ zYEwgp2R2fzQI~{!dcoWIiEUCFmm4xS#tkpUY2bAkT_#NS7$@UJDW0S31j}8JTmD|8 zle+<@$1Cz6qJ{LnW(wP}&`|u7f}^YFH+j`4_!M35Hj`glK`@Mi^w@UrD8w|*3F z=O_~xHZXjBb^Y>}M5uV*DT69SO@_@`N^X+th-t$Jj!APsAg9Mn+gZafarLf91VNBS zU}&=Pi~$|d7$M4XM@YjQTp7XK7T{3ix$5exRcPSA*vX#8(@~cTz1=tRC5+np4E@^gxSqES&ib` ztZ!l16-Hvlk?BncWgMS2G_&UzC@d#d*Ob)HPepyg?3v!fPJ+A3B58Iw3py}carpdO zo|XRmj;@Jyh9F07XZXC;Q3%hZvi|dig!wn+j?7^Ys=5|R@8JILc0UA*>FXrQ+ke|$ zdw;~t@13LO@Y5VNP-CDvlBPSsOOpDfQ+;Hp6iYl_-X79=_a;&i48kL+@m5+WUR(Ug zRI^!`Y>l{I$yj3>+uBl@k^U%1R88_@RCFG#w_f3&YPQ;PO+F`7kH`w0NkTP|G)rKjZCV{P#3P1ZDkVC zyQ~QISNL5r5jfw|L9Bu;Frym324q{pY~heL)(Un3C&sV8uy9kr^Py(|KC$nJEzE-p zMttNSUuGsxOV8ApZy85REw>b2dctGS`1TT3rb^b9R0bP;DQH5+A#`nygPf2Fx4|HJw7wE_zp0@o8N+Z(?@~p<|1}PJc`NHb7*DT-@Nk{{P3? zCL9WW8vR^wPwxztB0+8ajAtYn|K_)Zr$e`AtKNtTS{+YQYV{zs=+mAinH1I_++448 z>Wdzb`-j=&yMm*ts5)nXddXqx!9ymm--&3SH&fVo?JF!1ksk&l@yUzPNE{_}ny`#N zb(ATWs+EK4>`VW?!ux~XEkDn0dOM|IGp5(abg6IJrL3|_s z=$~3n{?D8`aEJL_F6$V2adCBps0{M}R!B8!*uYDA?PL+pguzxS0p={BC#*7hl$jL2 z&-?1N`9YO^P+|zep&>_cRfUCHKzoltKE@i_WIF_1dS=N(`Z%`0TN1k z0A?NBm*Lc(n1Z`f6Bx4a6hK{AxS(vin*>Tl4H(;o?S=uOeE3aVeZod47FsDN#YfEN z-AuwsCX&`T^(1d?MP-#W$_rf*eG^v~hjdVU9z2~~gD#E!W4}ZVTgD63>r2=*c#&aU zPH`09WM3gE%B10Ghgtsn>`25p%8Bq~(QikZcdFPD=JPMLu5uVB;}V|7K7TC5`1j;D zy;Z~Nl5%{~IOpX^`|$4XNt=~z6~b0}QKmGd>}3sC(KoIvG2PZ;zdpyF#D1+q7zHF1 ze_=-_kTniu{mhprJ}PgQbH_kzmKqD9AMRG!`KoDO@EHSG-l|tu^myTG(k(NBA_7H% z9z`ey<=E6u+wozg2`5{{;`%uhWaB1;VG=`U$GVj2E>VpkH_Q02dr`PF?!EG33(8y6 z`+~J?_wV4Y#SZnW;wmEY;6x_?ea^&<_xoFQUN7DrqkUk~Qk0hc1AY3#KnAFej;5_| zb@gvm)0a>$-Q$A4R1CDdRCsu=!%==T}l9lf-G z&jLDiwt15AePFGC{+s0sbpMqlu>r*xc`=?}Ki5?G&YvWD6fB`(ihXOiMCsX)=m@`) z(7SX*rjlAVKNT_&A^3z+V?<`i+s56jq>}}r+&cE4J`l4LK!ZviKN@Izd@{Ws$c?sM zpnMS{YsrThwEh{8;2?a$#-vcV3=!u+H5~a^pQ*{_3mE_fQ`PC8 zxQd_&Ajas`$Ub~-JrDp8`FsenHc0I)1-($WkCa@5INlPUB+@n|(Xvml{<|zeL@#nu zETkl^%&BpsB1a!Adg3PHLlG4y%Ur%46+KLAzaJuVe@uEzDco*&4}V#*dauBMxb&IN za?5T9oG_jU5LEDNdy&@3S5hLv!eo>X$)e^)3N_sGYG6U*HXKp4&CUs;kTc`s8?_9* zA0Rmq>%u{A6BVJbBNFTTD7`WcXmg@)gsRgZ^+G3MtTk!+;vQuqLTvkosZp{1%ax7E;c^k> z*I+5owmR!H1))mCpgxjID)R-DN#E6k0DeQTA&>+Q28HUvGeWpv(Yt{{B46b{^{%Y1 zl~icKpw{1*3d?vpWw@0m5&KN&ZlQ$bX262jx&~E@O7b^_A5bg?Oy*KK*VC#9b7Bc^ zu{XG!D~lQGZvsyl%`j*ktpTZDaoQJ4$Yi;XWTme1Q0}pjF4W64#+vjFWp9A9{#3x; zqNDYc(5N8bwQ~5tBcz*kS_zny`gJ*j{X7;n$H9H)-sez+!>apL;0K}Qzvr6~*+e)% zHISPWt+kx+D1V46R&xzaSoy&)4h_4J_yWb?{9pc^6Kf8ZB&*SalmmZ6$5*)WRsMFK z!?i)Kj;W+osQrS_H#gVAtEZ=anyAm#b+rvLKuF@k2c~>k0Bw9-ywOJk8BQbA@G-*O zs585F2EDQ2`Z9zz-MiW`1Yvaz3RmCJh!$^bzN2cg`n$A;f*hJT+d8_lcI;fGdW=hP zHoMc9vCe~mB;E$YyLN6w=5Jc*bmol$KH}5p%x~7L6re2MaYlb%y+RM;H3~e=Dq%(d zAzsuBN(T5B1qDN4EH4PLnEkFCi9^rf?*V`kW-0NH7*z7%7veq6Wok7(NxR%9z`n9i zWZ@^veIh6YfP3M@c0=$z=?`#2_YFuH;JedkHe`~ACdpmwUbmaNhFkFBjs?h-Tg!Cu zICOP<2U%AuG38z#YT1|S>>xu)d$A6+F40=&GNL*yz}jQHVi{M`hz-uFJ~vOnfg~T^ zq4iU3RzPJVj-n1@|4|>bKXgxc&G3ZE!{!@B%1(9SxC$DHtv^n2?B%uNb#`aag{9!5 zc%_k|8ZMyU%a3~y2m3mxS^Fmy5cTK#o3D;oO+zJkaG=+_=Rb)ZVdKh(!na&lU^4PS zvZ0^Rs(>bN7>;4!&36o>CC$Sfq2GE-W!iuYWP8_2l1U8(&=Xg8XyKS5%~cs&yd@NN)d%&T)3NlLWf}Jz0f7tUKWT3kT<@>q zN7D5ypKr2Y0DyFzl`hlh5j+z23KebVEvS)M@D;M{;|_@W?g3jmKvb6ik5dtpBI`>u z9(n43-~rYyBmx_ax$*cSFbTU8hyjV(*rr#81>I87+8sPvx&S;S(RbgxM0!4tSK@3c zY@DD^ObvnBgW@EZ(4}#I5NElhyY(uyR^9U05G)k6e*RH*_nMLR>#fhSsnb_IAVN=c z&v;9sDCUdHzL^>@>RUy*$f2w;jd^T{TW*aIqg%(zOf(-srh6E~NBFz$pHyyOR4rF1waZ#>OQ+j}{ zUp$zO1XXUv&i-G7l4?>_5_KPKZsl-F!VuS-!K%tHt62+={O`2Ke@Rg}Po3EY=U`dr zf){rg6?ZK2Gsd!FOlFQtp~^6dX{;G2zeUZTpFXuWO)ffpl+Yg${>bChofz@zGsDS}{H*@|@iwUJk% z6tUN=9NY$mGNONm@8tE+j7W1fQ7fwyKBOl>RBbbTGuWb$cjHAgSILmx&*YAwhbuPW z)C}dAL<)}IdfF_+W?Hog2D|$#7{6m&&|^0&x4#}=xXZI8o#?=J zlo#L5kj;BcuOYRv&u3U6h|Mx(;l3N~mA|fMg`K-wc4n6?ty}pV&b9QC4p^J)z)H!L zp?kwe>4gRi+C5-L)2@wM(UPJ|r#C*+QjxwM*L9a)FJxRNb&Hiu&5+!{K~CjmasA z(;hcGQrzT9mfBE2a{*3$%r7mX{O>s<(7HK@u%0&xmKZ0xg^P<_2Q96LQPPk1czj?h z8=rrBuA%o`E&j^a48qI95<1a!%BmvW@=~1&)r+HAQO&>!RReuy_O1++TFY0Eu~35b z7L4XP^wU|o5}D}k!kA{4CHwevN*DC%DBQ)B7TKCgKcQ&+Mbf5R58NqwtgNwGu_ZgB z8uI;Xh{7wi01cd@@1JwVlV|>*$pM>|!&1V5NqiFPa6H9@Q!ef|DFPn_2Cm(TJt`g5 zL(?+SxAe$~E^dS_ z0v47#?Ck7Mi1J!v!HUxiqngIhcPv@_hBPLdaQ(rL+cGoGi8`GKjUo|Z8fET|OPI>! zra)_Xp`T_a49PO~j96IenMwA~np1W3QDok$u@%Qy{(5R4IVGgvv8+SlxYn zouGKm$MkPLoTb*G{T*^~Tzt^YR5$y~)l5Z#7f-s@&(|vye-l67TZ?-AC5G(a2d{A~ z&q>OIN9muu(eG1yLoH7JkOX*K8^-w;1Sm@8%b>2S7^@oN`-YP-{np~8* zJL>`QR4NKHKGs)NR8I>yW)6j*=V}q^lo6JdFPXdF*oZpl^$1NQz=GmJXy3Db^SQLx&4YGfm z+*Ekcf14P{OK_O|Y^13?_U#Q+opd7U1-kwUe6=qXpUjg?dtoA0_C+z1K;&3&-nV0u zpZAX?J*bU{q8mE0y_Ia52AbwTiu$DJ}0; z%8Y;iQk&P=MO$A?m43P=GE@xYDq7Er5C^Cp#Z`)t8FdVQ^Y>o>5WmqCcl4@FlW}4S@~5f<2ab z9kJWop?AjQo%X)0&o3$2|bKN9XV}f zC9xg7+qXBqY$#k72AP%TdaU?ZJ&7DRBoY!w>Ya5b^@+l(_=t%z2e7dUZhW$T5Q~oX z_;YdNIb3Ii9XTlA{Ol#0(E5_6rxDYYh1|?49a4(H*D+}B3tjWmPN@s&=g>OY~ zkf7#p(TykB>-ZY6_83XDSbIyXK=8JlS(2+*ZfD#-}*_ ziSnEr^2VnhR49cdD@3Q9wYj@R1ZO13YP<2$UyY4lhmtV~-Ltj5f742p&je2EKRI0t zD%0#UFkE_x4qLNId)a-B1Ftqqq*73l8qL(Q->3HKuS*F-nl89Dp^XyW$r1 zWyF6qbJCpiTpX#Nqu6w7#a7uz)>HfLYj2o*GxQn49>Yj5ws?wH^<1jj@w(_IZC~va za3C&C^+}KX`|KH=V%hT%Z&+je^WCr&A`uDHBI@XY+l1I4T)R#wSG*HfIag9mg+CdG zY3W4Ks@-c;auEfGhT4+#NM1N!4b%^1$Zv-bO9(a(Lzqcb@Gr^d{imB@BnkL`2#Ltq zFB3HOiN(|llf3qIu$yTWbAfA`VV)DVQ54*j{H8=#8xu@^7jr- zJ>qSIK!6Z#$_V(ntV&>s)5%?dPR967`X%D8RNJhRE&B2YR~TI{OT>(d*Xk*#>1#js z5MiV*0}iBiXuRyUAz)a}k@Uc#>u52^m>OZIEW{DR}sH<^u&Ubh}?5_o|D^}1& zik*!BjE)ZZcXeW#O6WZeXAR11-o^2x+zgltO&x`jjNE8VZ(++i@x?sLa_Wb)BJ-&tvL0t1L&zB>dKhBUf?pa7QZVtNf zt!Wkt*dwp(4=E0SFW7Yf37zJ<2>9|3&Yvj59@0w^A3jdb6z8u)?1Ri5;=)&7+H?? z{G4eDKO7@3^X0(@67SqR-K}l)(DL(WY{f(Rd;a<8&{GeL4~ij%=|~)u?3$wZUYhUE5!MW4a&_L_Kh8}#+{LU-zdWH@#6B)Oqe7D=3V68tdRrKJ07Yqwtm ziYUG{hvM^EB8?=sZybS+%FDP{JDT(xW*@HfIBGEcfR03^uZ4wuSNP^B7G*fhK4C5g z4U`z$1m&CMEv#(4?Mh+NA~zW$skq>=?}!XKei0|JQNP@0Elx}?`EDV1C@afVA__y- zU_-y$O~uXhX-b(Y652R~W&fbt?{Ond-=d@Zlh!ygiZ9S#yc{+Fi%m%OeSrkl=bYk= z@BIqL+~oQBQsMSm0$6w}L#yA5kVF4?$2atk#xC-PS6-#~J@kEI-BEjiXcs|>DOPx3 z56VhAB0q>Q#htwUTbmBvJ(-!Yxutr_vO1NLpAfX6)|P4P2ABUQzwnO40lQ1s`>lI? zgtyTY=(Ti!y#}yBTSaed$ zOr@{sjJ3+ngqU>QnC3=+G?%!8$49U8<*SGddd+n7NXLwg%zycs{y5-8tSlU|`46}ri^em~>#5QQS5wkNN3-_q zBDMAq7fKX(2RxsU8TlBA`^}c=1Ya>`Xp{UO@?Aljv~tLq`Wr>WsxdwdN>9m&R)WTc zUF=^4mVl+DXhB1P-rYuvm=NwtU{C9&Fz&jJz-2qI-cgVz@n0aLyuM^itmN?XpQON} z8_ami3s#q<==&-giq!C~e0+bRt7ckRJv*EdWfA>jQnZIPx~*;rtoxvBVXT)ijWrOC z`0__RrwYj4GZ&=I2#D(VO~DP*-M?}0C)kA9QQ>%y z&{mx~2U%#HN|@;{Av<1iuba@!jHq%25ebQ?f-i;t5>9MpxFnQDeM_jrxJjrZOZHLH zW&Q^@83?(>Bu75RHjcTnWFs6 zoB*bT;*~oR?8kmnfmshEMyk-E^Cp!YCEsmi23n2f*KIl1GpX^w8Mi|I3&HjiRtE!C0ntl>h! z&k3!5>JEiTVLB7`dX?pWV2HZZ$wykGC8mYam+eiO{7~ zk`rX{vltb6+wA)6@WvBLa)2MN_3diqGx> x>hlYT3-O8b332f~r+fyZIe-2yfV-!ivqSLz8^DtO()1YscwTmjHS$*P{y*T)`riNm diff --git a/_site/assets/img/fortran-logo.svg b/_site/assets/img/fortran-logo.svg deleted file mode 100644 index 8cb9dc716..000000000 --- a/_site/assets/img/fortran-logo.svg +++ /dev/null @@ -1,98 +0,0 @@ - - - - - - - - - - - - - - - image/svg+xml - - - - - - - - - - diff --git a/_site/assets/img/fortran_logo_128x128.png b/_site/assets/img/fortran_logo_128x128.png deleted file mode 100644 index f40293f5510e71602d9dee8fde3872db94882c69..0000000000000000000000000000000000000000 GIT binary patch literal 0 HcmV?d00001 literal 2977 zcmV;S3tsezP)l#SnSfPW z9qmwB9sw-~l(DrIl%g}$B!dnE!q^IkL@iEHB99~>4?!Tw4SC&r_wGYJGd1%rnD_=5@&z!G0Vx2|0B|ePNMK9=wF2-n z;5Y<6XAtEfVE5|M`A4G-<Z<(bP2~Os36ZOw0r@Dq10mh&U<)+iY^Y{M?&!t0D=| zZv!kWTyq15>q!9j0&qo=sKRnW0@x}{bLr}`1&8``VAuxu^}T;i3$z4($H3-8-FT;B zLf}Qsa6Pu{_1U%I91xZPil(i-9gM#UU`SN*6n1eET>P~7jrs5O^}{|ZXhqZ47lHA2 zpl*IFkqeXUE}HhjBYpj_mmEN_MTP5^3t*9z$`m#u*z)4iIgbNObho?5vV2it&I)z& z;{b+<6AC``?yK0gv%B5h8lY(U`XT_&$ke5<5r&Bq3Vv9#ui~x!U3Xo@;=*;enZPap znl0iKb`j))-MON4?w-yYuQ0%)(^sdvgz;af3SYc(vZW<>{hGIbRoA}ZinjolFqS~w z{CFnU?be>{yrClpXlvp77^;yc-U$MHTye>qPk~N3KwI;!y7}>s#)SDq`#%h5?bs3A zbp#O_VCq8?a7W=di}WeN;oXvhD0^vdq=yGXjO9J|=G>~*9KgjNgnIfD35^3Yfwm$* z2=)N29);a7A!YyoUp!?)9)QurdKC7Pzi8^35!}?wyQq~Yh;Z@ma3R=uY8?t1gka-2 z0}7~xD99+_0%AC|3I!P>IBOlbt4K`JIDjN-6$&y^I8?W9BBNPy^UGe^i)}COgW=Nw z0EWj6my5$~XwVG}hEIp#al@NzAR{XoIk}k_`_19dba{=B&;IOh2nNj__Zwa}T)ed* zRMTB>>#di9aRyJ@c>sXNr-Sp>J~Pejg6?s{Cg=gy2lM)vVr7uFH$p-kecc1 zh!qQ1rqnbA8ta<@pyO|EWagw|=Hki79i3&Bgez#MZ$_vW1B9b7QZlnsFmmi*6x^JP z8*Uv5&F$P)cCu+(7r(5-#%Ib<^Hn{S1ZiA6=STVO3cOOh6H9)v2|KoyBiIt6menn! z^Y$9+oAICbqMqL7XzFVlv3<({6hHbJsw=*vmeU3DiJRw7hc$sE<~e`51{cfIwmy z000{NO?YGDzo}&aaDV{<36=x2^I3T{4u5olS_ZuVOta^A^>}CJYadcepf>=zowAr1 zR2@ExQ^(GeY9Kd20^ffCzz6RfCQYB*0ErHDy8wBwg%Hlp0|pLC!;D4Whd0^i*rsV5 zy5a8f+d~Jc@Q>$r^(%hOSM@kkeF1}p4TxH6B#;}x>19A}UN(k~3a`UT_jENyI2`@t z6qx~35zq$%u1S@i#;MA$q^HpnDg4wHGeimR4t!0eT^OXu54_)m>_^Ev?Qd1N6ez@^frUtL|cg<^T?^0w8bPP}|a~ zO;iIo)d9l_a*&ywVq1ENn*&e_=z$48xZc+E{56d*P5Z9~xdEKW@G;lm<~#CjP16jS zxLn(4Ynp%)4B)ULAZX`haAlXC)&uI|b=kDagsqfXhYx43I)^00|xMtSx4PzX=WgCZLBg_qxZ85!YUW zn{La)xJjd8YKd2?h}$z}jP*I`q@^iwL9Ka%syJKrPK6>|v#cG@jy#XY_c;v<^{mUM**}8T^ zZUAZRKv4v)uWQ67dyiYE#lespKo*e}0qq>vMZ0>JU630L{C(A|Gvo%4g%vpfK(}y%UBs^eEXrD_ z7H_f(asya(qppTql>=N-Ie=UoTn7MJ2bIJ#^ahZGRdoQnX6aH9wzY;`ay$PFOtN!8rS0O3Gy zfNs9PX-QmF1cU{>0VLfhk588pH{KvOK%}2r?F*^}pJNSj17r`8^I@jkylg3P;|)>+ z3>=(>TfTR#l-Of#%Eh4JG#_M+B}fdw7%=u*BQS4CAq=maB7nO%e);s>$iHzY$;TgJ z1y)qJF6xEaIA=)7@WHKX@c4AN4GnHxgEvWs;nm?wG2lxw;7vA=n&HFH(OF0vVBZq$ z{!0xwU3CHenufMjLz;2f--O2cW`sf}ni^UV41^G94x+g!05fR9U)z`vQ^PEIS-y4h zb+~8F?N)@6LP~}Y1sT469aDAqEY?2$h9pJKfdhzo;CnnS&7PcQ&o_gK3332Yk9y>B zxYAZUo>MpYxd3XTjS`Pbt+`wYQFE;2T%a=ADDn8TB*b_EhT~iS6;a2rXaJ^@a3#Qa z0%oFuGl+6(Aqpb6_>hNy-PAf1M1;&;e0AykqhLs!h4B>aRIDs}xRL{aFxe~AY7{mj zuo-CU3*aL7cK{($K?*wwLNhl3orYulyl zAPCd7wEdqB1FSAva0tLU5=jc%U<`jME}Px44C)oF9h&ZX3cyL*RVnPEnw!Qmoi|)z zfMu`Gt`#Qk0}%fm;fY6(3--YB(x3Y~Z|u_ExvFg5`w(KWeYzBOAb>|#l+N9A_4aPZ zWbdnZYyY>$-0fw+B>B=5Hn4P6$-F;yx1+}%k5wgepMYS?A?Ri75I-KmZF@mCSpgw;zSokGpu<`iUkJTL9!*B26KiYGLC3Rb}(u z@9T$Q&CA+bvF+r{6u$`cQSQ}^w-S_;q1!1jh)$frUMTHx#142&% z?8i{Wf>Q_r*aFkFv~wd*I7B>@r|6!w!-VOY#e|pvAV1PLim0f7z-DOXrs97tsE#Cn zC1bf3{%GAuS4i9?1RD>a0Kjkn=>Srpii>Co0jL8|1BOZne9o9CN66f@vh3lg$8-J< XPr30*f5xk_00000NkvXXu0mjf#~yoW diff --git a/_site/assets/img/fortran_logo_256x256.png b/_site/assets/img/fortran_logo_256x256.png deleted file mode 100644 index e41a199fb6d52033fd95d4c0c447c5668a0a7b16..0000000000000000000000000000000000000000 GIT binary patch literal 0 HcmV?d00001 literal 5990 zcmZ8_cRbba`~Uqq9FCQhk?q)TBQi5`;*^n)gt9v_Q$|Kv#|Rn6mKmWkvw9;V$CeR^ z>=79enc4ha-k-%yzbX^Kkw_l*6Y5m`+A|Tt3gA_MhO6*(bB{k006;52%yN| zhnZWxE&QNx(Y)&p&)+%wL9FwG_hI6NC)Z4#+nRVc_Q&~fEg)#Y*LA_h#6Rk?;~k#qUoCQP^Eim~Z)BmLN_WKv2&NPr^tPt50@ z39nPl9Ec&lXX4`@zr`z!?g}BFdm3VF*AjO9dwh@_S`ke0#pxj_UTNnSWS~UUj2Xpw zL?64nR zp=5Xo%~E1?4KrVK{-c&dPiB$y)|WHX+j+-5a@tLeS6CdMG_0zqp0>#hcLz3>C1zFc+Bc(S<(CGQD4#H4J0jh5vK z(fCRep7t=e{0B!V4^$$ugXOs>Rr|CY@&sc`I`9WJpbdxO-kS~ouV-dTS5oM>EP zAs5%J#akx#TXfI%ZdQ@$bV-Yh?Xl+7 zh<{~bjJp=%oAcdxFDW8|eJVA$@ao%Yhm5LaS z>gn2#vAD>a#o6l=-s$;PvX{N9TB3yGbArYPsa=bojMFq$ItE|EJJ0ntM+Fr7u2iVE zsJM;<<1P2Q$SnUb`A_VL-<+o{pyvqS$zmO`rNu_?J^HlS{)xpR{rU6EkTdiu9%n1riQ z>nbz4V!HR(k`=h@*6#>_h@>`Nw9?I!gCLsQ_)my%665?{b*yK+?eA|y@;VTY#Qa1v zv@-!KV1SvqT}VP77ag+ifT6^-(X0qUIhr0^Fni(J!_Y7x)=&{`Lk(W^VVh2FYwTO8 zn;vv%gC^-Cp=3t z9qPfJwKolE(3Ox&B*Nh6>IyD{4k={+MYb1y>tuf(#+X#-wBUFG%;Y4}q>))Q z&lEQ)cU0C!2m3=cy$n5~@G@69{E;{6Li+Qg zoQHb|f=|&~r16oZ?3^H5jLckHg#1R=!eq_n7Ry{$Ux1kNb!6=?$CzxV#Q9gItnGOP zIH`g>lz?=k>-W)p5$#2Z_rmzVSt-WG$r?uT>8G^SlRmxK>XvS=7TP^!KW+KNTBB_9p24sCpxAF~W3|I5{+_s3`Iuc=I&Y+B5}b3?s8`u>a3BkQXr z`BUyD9{l1Ts{qJ;)@NP+ccn3(a8+xpaaWQ{bUcFF&xdNtXSZfq;hw7p1c;*PyZHnR z^X0N#6qlJr;9|fD*{thr4-WB~PvD;3lkD7oO+Bb9!X32hO*RC%KH4P|vb#98?I6MS znx4V40;T@&FrzDxwItDnxe9Dl028yYIOO0`ax)W_MLfTt(3rEW+ysCe71tqp;cK-@ zKIs%K9@&t0yCIskL665!}{MVoA?@?SXUpVRdMrt*tS}Wgq!=d8KFqPMWXrrcV9+~UTezfC|h!C6d0GlK?c@9Oh@X>7-5aJBt-sd~n zqHH195wE^foVmx$a}^2OC#PYEvknpics@M6q%s+^L@HHjU#?<=xT2XG2Of#xyL4K0 zLu#j)0>-}0?d9Y~-G}SXIuRA$PntiS9p+WC6_ zHv{m^8y{0PK7X!p`Evfep12{W#>X^24cDd2U8((}N<$4T5oUZh>Z?-fVvQC~(psBW zP)CB;TJYS#HOx}9ZBFp})VDm&7R&z$u92g zrWMYEy=Qsdm%X^}LtxC3oUUiRg?k;H^6QUZZYW7-Cnb7t*XxnL;3j2dtSRet3u|U& zJ8$=a&ts-_0|z-g%y`>m-v9`4mHX)G#iOg-K^Odo;xut$pjSshNJVItUsi#c-%W}c z#6^~aaI+{lW8N17E(ZE;7yl0p9LY$2WP%f1n+d>5v?F-_|0=M$NW!Ci9uBF@z|MdF z&*T})YU#mC|uSKWuPU!|eXdy~?2Wm|9j zs!CrPz{fSle*39aohPJwXMbq_J8BNlNMOqf&d@V z81+2{U#$sGjo!&sK;C_h1opC`W!CwpamNojt`5<6qL-&{>SiAdFWW2dIPHvwS+`#n z(NeU6?62=g0k8xo@HI^CGOG;)$J*fIlZL;4REiZ5ck%FcLQ!yvwVl2Nb3vR*^XXjn zblu@H?`1%bU1DHSjuk(bM!8RMD zPyrN8K<#}9Q%R2}sjL9o^LIFj^c*#}Xxbd!LD0-@(&M?(07aX9H>cfU(@#2zu$*5G zqK;iMYN*OiS6fC(6-foKxz+y53a%z9=QAtfx5`2G@b&ptb1=X{1)eeC8NDD)OEF;Y zL9Jg@fnLNxn9}HoI$$Hf3VWA9OrMdKYm{}|XK z*G*vCun<{h+R|+}VYwA)mbNNECmfKNBC>Ti7Q7g20*elCG=b!yDhI&Z@8HO2=YMoC zv$4F@7-$D|Y9G{Z-PU|Z4`>nb@IL)Tz?=HacxQ;)p#I!{V>(K5Lk-sQ;t6WlY0+@4 zU}FPMUfxeF)ugFz&JGTAmNXH z?%&#T0KDzZ$X7(Xp=g-eXJ$my94y=|#6^t>oy_~Lk;Mv_nFC|-de($@S#K2E^B;te z)VTgK%e>NpJvZNlfHThfhWP||O-vCXzKm*7r->%=&3qYH z&bTG%s?GbQ!5&?)HL#_YM)>|{aP2YiYua4C>O@G@Tip+@mawMoLW=k5cpr=%r+h{b z*dS8rBi7rAG;qQQ=nu0BZQNb??~>sADKN(82bFgm{W%`GOw~rgvSa@|(TKG#s9MEm{gb1?_WYr1U$|Q51mVh)F0!3Ix)nYgu8G;^)bRy* zPhepzjIfs>Xijgj6J+?H2SWKRa1`JOh{b36^vs zi}}HL#&^uH6Zjneszn!n7_gAOkF>_h6Del;cLjL{hw7M(-591c_TA@V5H z4cQrTv^~xZP{D8He1v~Urc(H>17*r=T8q*+E^5mUVZ!Mxh-tkyiUjnF z|Sz^lJ$`DMAunsM!RdjfTyxwrRG#5r=ObGUddSNrywVN!1n9g+{&vs^Z9fZdDM)n&n5ae&Jbc~nCP0a^Jdmn)!_@f-u@t4 zcD~@O1#;`#F41b5^#eHTN%`@vXAat;(Mp;#rnJuco7q`=oNl&ZY?e(e;BTH76aAZv z^Rp$20ZlQX2Pd&e{adcMiP-xhV9F?2Q|~Qr>%duCM_uJdl)F;NSjC8S~OYtco zG3X^VqX?QepysXHXY&^ikMPLdxqFxYe0^ik85Y}b9~92O&)Yg|tXl2uafzz@r{H7J zQXiX7GErHev-18^?33$4q(2*D7VJ;;#p=3o(`{<(P*1sID)tFwU?!UDRBiwJgRo+g zj0Y`$&lGpQ_UdD-o9rHhMi-?5qkp4!%p8Z>Y4es|O<1Py=H3mpejnB<@W0+*TgZ~pn<$xd>v&(BN|O~rM7tzg=U`>kyXqW|k(CDJ8zdrZ5cT#>-+OkugXqVa zB8?AsvANi^WzdRiCi%Is-#s_zTWbWTguW+EBxCr_>jxp4$$sztn0@t^yAD9Suq+x^f7qJA>Gv+|bR zz*kFig4C*_OAITgL^|`*RsG8G%)&rp5#{R-fUNevrs=xbKlmaZ7aIKiq114(K^{{7 zi-9b?HTwrd_9uluQxFP6oBJyfygy}#(l>!XtXm;oEFQxu*^H+q>AaJffWk=gj6s#= wV3i?_}MZtor*?vVqnYr5F?YF0u255Pdu$p8QV diff --git a/_site/assets/img/fortran_logo_512x512.png b/_site/assets/img/fortran_logo_512x512.png deleted file mode 100644 index f3adfe7f06ca665ee2bbb09b68ba9d25526b66bd..0000000000000000000000000000000000000000 GIT binary patch literal 0 HcmV?d00001 literal 12591 zcmaKScUV+SvuDo`1w=#;P(fY=Ndf|5AdaX=2FX#7Ad*2Cau^W>B}zuJ+90069_TC+J*M!AUw^)6R=UXe|)#Y2!PCbbvCB=5HG%y%qrXP`t2`SWk zRqQ1pn7+6{Et`$FIIXbzmp)ARzVDLxNPFWU*$-1SosU=k!Lj`lmQm{L;+})gT|4|P zi{+S8a<8uJDySLnUi<5(t~I{<{glCs)=Yv&;c4lGo?bf{_MS2Ih)`wWHsy%xKhE`X z#*uyviMp<-DJ+;9K^O5y_S}@95b*nQMV3U?O{e@zwqlRS*ZhbDT@#zq^vVKb`Fh`I z=jqb+88LgEn2|42-Br{oO7E1c-&FR8j*kz2bkbqAPJcluxGd0Px>8DvQ!NgUmUq`F z;b$V$hgI&xXr{OFJ}R21t0UM?`QEYO;Cts_qIf0iuHuIa<^^N?X~ znM}`Q(!!Y?)A`qgvz`w11eM44QL|||IbW>|t}k6P+4zUYOQz>UI4#~01zxf9TfB{8 zxt>&CxEVIh5&!NT1^({K`+q2#I^x!7h4U7_N;|(Q-n=}J{T+J+U|0uaY8s6e_dC!0 z_Nm#K))~bURnvV%f9vb}WAmtQJJomHLB}y9T>vkH0&o<&`aZCQ$%R03~08+T3N1*DJpJtS-LQ{DATKfcTYN$ zE1V1KF`A0uS8BS5K=y@}Tpj7bKM{#H^(!adP!GE8t89`OwFK=H=NNP*SGIWS^(-Mo zx#M*H`LW!`QZYR<?7|YJgADqsvLTI9X1l4SN=V-Icna2B*%Cfk{|q(`!kn5=V$JPW0$R6d}Uw3n81WBH&>rnR;U4Vq}g7UPDp@Q-d06bJ8+{;sCJ z7RJ-nup-pv!7sQ?1lqpsQQSCMSSX!23?#4;ofxHR%E%fIlVdyM7_<@WR2Wx zqUJ9b(Nd}0z)*DSmF$k^zO(EDWOcU#;2O-XMVaq-&j~~o;U@v^(X6mS?X33s)Y>5-X<^rt0&2hCK1KcXC2;L z1SzY{X2Q#FO6~SjO%uC5ih8VMGOa}v{FqLbpZ3&Z0>Hjmrm`X^)N5rr-W)6He$Z39 zzJ6ZytLc7ac$dQpbVh!k4_=ziP%)U3N7jMsiMI=Lg`@R2t(5pStcU=OROn~x`TV@4 z9Vsg=!?JXe34+jc@O;OZMB8DHbjJrtvY2FFsrZxaYAZf;x7OdtXishLiwD@z>w_hRbFG86SaS^*%ZYRg~$BT{=tZ0|4n_pQ+$sL`vZq z8p_oPtt6pCkML@?FM|N2pqZcjMEUea1o~{rsPNNh*T#Bn{_NJ7o4LabiBg!GZB$z= zRnNxUxgZvXE}CkQXk>`lA^}EhB_zsO#12INj8itzn~&f6Q97+-)i=9Ui~<2EST~a~ z!d8Kw*C?^;+}zFdAOV+a&@d+Aiv_Igjs@$@(l>|>Q)uyF%e#Cab_IZM5238xB~Q(c z&?4(?GhIIOMVbV9a;CZci$A@-`|LU8zm4~rP7u#$&|}N#3Y|m&oVQKedB^OFdnoBT z;%`pIYCqkJ4FeHjr3A0$A8Z6Mtv&E$PCm_mi>_H24|7_O2_*u+xl^W9aZYz{S>l5E z_LF4cEhDS-pj+c`mTH?@3ya&v$3TXYTi{a?DptV6TcPDpf$9)|NZmT4&bqf(NvLXp z!rY@RdY-khU*3`cFuqO8d@^Vt_S24KfVOEtXlCKzUt|9BIhIxYQ~*fl^F9h-UO(_K z=e;<8liG^3$-UT$X&(jb@mI{BX`Pxm?=MDV->h@f`y1ohH~U9$3USj}rK;&9d6x5S zl~fj_hz}9C>^S;O6>b>Aw7i>{nfXuf++Fw8KKyid`)pWh1`M1i(fq|7hh*lqn^f*6 zQszGE^%SIu7{)B5r_R8ycS?Fzm#l5aZ=cd15RRQW zHjzD|;P9{8df`_>ZbA1#K3rS=^_BR$vk5VyKO%nDipX7hd&{uo?YaH>*evx|dKUnO zeRh6U^B+Td=Cnv>E9jD?dJ056diW@D0-J_jf$CSTEcR!&<3$FsQ~-C%c6&Hcx52cW zz{qa)r!#t?kj;e5y-R5e=z9+YXUU2TZJ9z&G0wYD=AC=rx{``}(GyILuN$8OfRT;; zm?65iiX)k@ni;z$+hfr{2BncIRo!xCcTWlqH|pf@?S!@^ z_d#gawK3H0==gMocTtO-h7w7L+R^TPtthI$W$uqwspR%~lPQg%eL z>Mp9NW#7?a6+kQe!qDM1B3Yq`n*G7`R8qeN;o)h^?B(#$X;Rz>9ZoT@rBSP=D*Tv> zcxXJ55@pLoBXpo!7r##iFeHL4Nn=~fBa5gMm@cWrb>w&*XVj5dH%(ghW6Lst^*P~9ASEzCkgwLa4?WRnBQq|@);%1DoqKn3c#!)re9E@glU(-*R}XUw9k~Umu;q_kmK{T) zhF}ldpc_=>2}Z@l+m4Su%BR=o4F5`kb5f+5=QW>jxCvNgRx3e;$Z<9JYlX#4--3eW zO!fVKUAf0}@D7|h$7qt}-ZCtG{J<4Qsw{XCZvq8PTk?{$Th7E_1}?^KT34K8%84-c zhMA!Ayq6G9r~ElmW@A4srVJ4QQfR#%!kIa?hW(nmoNL1%e0)pV{p9GA(Sd_K0OoJj7 z*y-e5-?Vy!JQhoHqUT^iJ;tDhUhBI&s$QyN%SrRI`>oo2-mOL?2NIpjHC;(oz^V$T z3Fa~-&h3=qXSyGr6wb{naak!N*n=BM{W5>S*_4b_}n)9%6Ca5=54 ziv2kC#q6M5f?zIQp1~abT<+shKYe9oAvPqD-Bwi_E%eL>2SBpiP#AMmt zqu_;^J5L{iODQ&L{%1S9)B}@T)spuIBh+tZ4rAF;erxj-7>>T*$kSW@c*agHT&(+P z&)B3>(`mJ`qhD&*EtaL_Zb`jB)BID|SR^%Q=vFInmghdLZn_N_2F#H)Zt%A zA2me-X|g((Txv;&i;Lo3E^Q#;J-DaP{>piDJ-BwG+0N&l$AxR(u@_iXhjm5PEB((B z>`w6x%)UCu?C`t6eVJ@aZE`8i;K5zu;`?I0H6pberOO9OJTZ7jW|DyXV5^b!tdZni zjhOvV@6GzXjZm#IEc1!ecToY^P$k|w2ann6C_h*RS?fIOYU%dIwp!LqnG;r^y&?)`_XjXG@ zjKr8bHp6y%p1Ef6m4APUcPZgkwhA3Cpj6X+8-E`j(V>uXO&^b^#rT>(mG0B2gZiy^ zNZtdCUBi0F)xZ!8C$_?TW8^$b5C7r#a{oZjFA-{PauP5A2Zdv^xVzRAbBlzAy5PL%dhhaBmjANn7?w^QPyjYr!eCid2r#0dAjv~4 zfzsCV-j4nU?1e}Hh2MyZ38Xj(G9Q>)>;u`s}C_>RjM*_mr@zi7YaL?9S0+(l} zmw&dB)L*+w2V}xa4Cp}01zs;~)U+3Y1zU!#4)GPd3%Pg#aL+b3&v)+5Z7pfJXmw%f zB2ObEbSNMoIhNd`g9r2!`n^Oi;PCV$D-__gE0icz*gE*lH7KBRg%gB*rUfcoEVVNv z;w!Z=2CW#T6o3iuOEg=g$)?-dUpT>QSTc;I^1FcW=b1$L21H#-=ARwNJNgob8sdV~ zUh}*`(LXV9jE5%M2S+j;1~U%0L>-1obee}8j@3En^(0C?wy8{w9(*wN=g35dYd3rxtTx%F+HmRKc5U6~PN6|2MF5C7&+je0lqJ9X2 z^83Tx#=@Eq;Liy-jZc7p=tjv>g@W_L2CcZubbwA^pXfUb=IcLA3Ts1950F8mARwvn zz@nHyZtsW2UAlone=oJ%aj!qvJvS&Y0XeH@JbEtUzVg)vni&}~W1sB(Tt*fbcz6$m zIqd;(PjzdbMQHLF%!rW61;HiSF8~@He({570y!tbxAg}s8sLklXvFEj`tPfNwFC~% zQX~xPw_;8-8<1gK?a#652XdIayXF?u5>%*G!=2-LDO3GQs;Nloy-S%+*k>}W?dn!Hr9_} zsUqR2yibxVdBI}Hri?&7^m~H=9!MN*DgAKN-8FrSgfFxh?Xvvwjty|h7ma%qbYyS3;3qP8`de#HbDqHi%n22!$9ga! zcTlB^yj^9d!*N3O2Y8^GUOH)nuN~ce6^#3ifsz&i_Rp1%eyw#$4sZ`9LWQH!pqWfc zUdXmf2Y!lp(L$HQ;sGobF`@${B0tKFNlX0)7|9_rl^v+I-`6o!D&tL57)D-?V6@5{ zqRDN4$^{g8mPh=_6ZU%dQQ1$AO)jl3_VCnA3XB=T zuLn>uHi<=%3;+8ZuyQe@g$h#zV@V9ay6DV+Zo#7uaUkjq z+!Y0ov*~cfqiCEHPN-CKg4yQnP})_oPxotJARbKG#SfI4fVE%$Y&ggg2iW8v$nqH4?rhv#7FtiM@ z>ZiiADPhPav>0leX0_T^_oj0d+&;{)BJ~9mRX*Lrqg42`NwXCYK}DZpFBvH-M&j@D zJHu7cLMU$N6)<0m4-Fs1qL49wy>-{e?U#B}8*+3+y&iJcDyD(RGkm1#afm(?&t|}! zO9#y<#7nqY8-hC~)Yo^=!jlwG9rFC2rz4*&a8UtJ645XV_FyTChpfM^P-OnSn7WEE z)t5x3=){b=8%gNOE3I$GQf&vJL5ivBoL}am|+-0n894h-3vYm)i=s#}KWETYb;k+~Q|ITCElyG(FAAn~6{IT(glw+cw zAGa<~ilC)&Ot`kYD9l^4lK=(rn|t@(rad#!x zdC2I1Qwi82h~{SD>$13D9Q{jpEEiCI%IB_x^yDPp>VY!L4`#=`flEx}xe8_~cT4EJ zR{x2m+qPc25)HUdkN{j^SE5^;v-y1EB>^H89jLjIt0*JCv7@(hBJ+32p!#t|WGN-^ zXq#5iUXz|kN!$9SV`wz!!#;Tx*Cus*mKpJ0rxMeV#giTc=9}tMSCtgWlQjigaQ$=L zYdSBB6VbRYuH1Ga1Q+Fp21Y|6VirD~RoldF0$0wY8THn5mPAi|l)Hlh*GwOE^v=y( z%s7?g5li6YOkJ{8S}aI}IcIGM`XY33WbvTLD($@0`q#q!h)t2FHwPb1Gz~|^a{_wk zlq6yYKQ#rt4UyQvBszQ$kkeu}XnlS;FS>9L8Xk-i$14bd+3`bv!Yp=BS)Wt@5E-H{|RUG`%8v;X_XBWxT@*P`S&^dEd6hoOnCzhBFu z@l)p0#!noCrY$9n@SASdSuk2QR!`qa6eYL@+h#j3lU+t!9RvE!S(Bg^W&9wLuOgOU zb9CaIq#IS1>*JWi!^#ZzjX1M&qNz%0=Pj?-q)Ka)TV%kZmY{4#UWA-^xM0#lcsRwz z9N#?^JIyo3*0vU;>a`henyc1qAd{out0pgxLj(0H7-V)^bo)c|`u(^}u0NKmzoNjL zw-P~!YiTahu_||-x&j0KSBnq@tYyqzOszzl?r9H}rE#MCu0wSs~5FN#SvR5LL0OIk5MhFw2d|&6Ul|y^)doE;84$ zx6OK|H1|rz{BW6IIhRI%di9|M?lBB6D3OES2lAS7nP=c|t~jN2s#QJGeRYvk?SyhA zknsQo&`y73_i96+)PJWz7<(ET_A$icEYT+i;L-~SJu$>k<{*F-xy<-K-yxLzuMiNb z4O|NNe+IvS1`F4$T3?0g#&~ zv09o%n!`VPayoevEm=OVnFuHgrwN@Cu8=n2=%YWf_-RviMS&^JN#mLJZJ>SwQVd%( z2fpFm3}qIhPi%B6b=qU{$9@qug3I4s%Xn0~{3DxdFQhlpt2OV5dM4Ws;Kx7$$Yrz# zR&HLew7lz>_sGlHZKb$)l2A6dK3cw<8d28$Awu1tRS-=hjBu3k4#gOP&C@Hh#ReYk zPUH!;JZ)>3boyKDF*jkdrS4@?KyU?eIOqo-?|jh}Xq%j|DCjR4)U^6xm4_YYPwFc> z;F$NyV#&T6GAh4f+JO}VD8x(!GG{JY8E`O(S!Gl{GRQ%GwLZI5V=nX0cbjzli=ad> z`sC!~VO*0sQJWQf;!dq=yPhD);%s!w(fg1JKHmMg$=&abqZ!jk9ztZ~2YoMhR{8w1)6+tz zS5`X&E2jhcNGr*&b~ApMq#l{2zHo;x<|+#xSkt zLcr@_XN+MZ-ipQ45U9N31eh>xkNp@nUibZz2k&S>Bs0`e$}@?R_MDGAR~1J$B3cbv z!8PdhSTPT|K=^v!vf=lLQ*{dv9^QEm1(W-^6gW>qP?=ge&e)+CgsPH;XO=GY1dtW4 zymFXKxTx-O1G-S0K?)rGriZpk(@N92@5Nd&mYJvtW?(pQ-ySj`USj`tpuo}rzEnb9 zGV#A_G=|oGYJZv^L7K0hHi)9wY5SRgtozFAn{gyS3Wj@P&Nm*Qf}1X%rSXV;PykRt z&A#V6rTP5zcIbNHsfOH;P6If579R5ZKl_?}9^Kml*8Tn83mPS=hG2d3AYilhOvMK( z+|l-Hx$b8pMy!!gB)Ip^>`jMtwN8neyoNC8#w|jQSOpH{!ymcspBy|5tYKO~9AFm3 z(k;GOGh~eRqeR5}02Rhopx6K2<>-T=FYX!=+>6_M7ErV0+dGv84`6J9qiEzo{i8Hk z!-X-|_w%-4nbQh4gvn6IMI^{)Ay7}T<2&X$#|*b)4Lt$+GYih9mN`cUM^{{mZ0AXp!2KvU^I1e6Ii$FTKxFk54R2dA35FRQ3wRAZCGLe)%D!? z%tXkTdlVY@p%9iI>zI-8j6Kzq(1O`ZfEd(0>l5JIm)JQsnn8f8UJ6AvDh>|xs+|f5 zA=y7&}ccVnLQhI8x+8OK@4@y z@<@Q_+AZezQv7A`7FLka_j1l9bivbe{D?XIBI-yR&6uzWeYlDx0(I1PLeX#nWQzU4 zah7*za;j+p3abY~pMcahpGZpvM%Y$BQ-t&aHKnW()Jnmjk*R73_iVKu_N z_|c;1CZM8*6^uCqYC-1z_v0~M{tGwv^Q67~jeLvmZ*ImLv@(`q^K_wENF!M`1qN)t zrEUwq&r@dl9o9i1{B1o$_Ymy2(gIx3d&tSkxK9EJV9iI2leEbP@=MP1AC0S${QDZ( z?7jlZj~)t#O5@Ok6kxOwPO>zPieWt;`QJ2_=r3~y#lQb=H-2z|wH0!nvDNQnFQUd_ zDTGE7*_pwjq<1Fxh@iJu+)$qXQvKbVdo=X#|Fg~7Q=)S8$BccM?9E;N&(!tzU^|2z z0C@M0Iejiq0KI6@_0?-?! z7$R1A7Iy?a1C3^#Xez^G+!yNAckwP)BisMLdw4%duXnkg`x4*~1z-hSWDf&h07sXA%p zQ>tE~cVR{WXACSHNo0_6CCb9m2@p+zU$gQ^xHO_5L<7!EwGwQ_#5C#f3<0SCG?2AM zQ>lu4f)`AGQ(;w%PWf-6lnTPWbRFR?EN0!2L!<{I9;~8a!g{RH#57V!O)EShk0n+? z7z$)t1+dDt^`+}S$kxW1I1E|i5kvk(|8Eb(3)wak=cU%bhs3V z!Tew(4(EhK%xDu%09GetV1IDVGv?Iy!AyoTu)byu9jt86=NuD*2iZ>}HZASpCXm{g z<-A~SfjKFw48#RU9S#|%C~EIZAg8xG`ow{xsUvXftx3*d@Ks?$v8LLl*;#;bRRNc5 zhf!zBy8rPM;e9#T9lHc)Lv>ubdUkESnBND}Ql&(D(x0WVGIK$w3r41}d#Hf2-Y&^E zqetwfLEm>ul{GbNhOw|-3GVd^WHF~710cq?Le8Fv65@NNZUWvLpsKl6>pe=_Y~-O#n4ysW!9Y&rN4+@m5%@okO} zU_N~A<@E8kzvX_q`=G-$V3pC_%{$oZ<9feP{HOwPF>k>=uog<6Sw@kErg-lTuAyy+W55d~b~gZ%K3#b(0|-PB2`KLtQje z4!H)&Y0rk~tfjP>x~NFntJi7QAGa~$=M1OA=lrO}p1p%V-IZckU(qZa%8tg`440)E zz@lJ(3H(F2nTIv0y-{GN)jG|Gb(#7}LZ;%(2~dL4@CGANp&8x)MZr6f;;C_=epz<4 z6B&Z9e;@qr?dQs<+!v2qa=WUQ$SvW2(&T%j0>^c?Woe7$mPCodF#c><-VE8yhZiS( z)wgS>mg|p_7TdT+`U^Z=?l8yKMs_pw!JI??Mj=G22F#;vGae0^U+DY#e;B+!k^>nn z0VQWVl*bMFu@+{zYHv79?fexyN|^o!-Vp!`<@G91uh| zh+=G7-&%yV1r>q$^Hv(dzGzgF4;>D5ec=YoE>hkHA($40xd>nN700vu)i^Hmf%Q8m zM$Dz=P4Xt?f6wVRe~#A?{*@*{bjt87O0skHV`7~=G}~&FPTyED)qmwN1sZ;foW*22 zxk=AIOT1*gosQlPB^ZO$@C~+hswQXTnLjBVfPZ?XbeNui3V6WxTbJo+xDArt-awWq zzQyqXc*|cS0)Agfm3u^BSya72I{{`rUqreY3$Soesw@B+*2KIEaWpyv9k?vDYcl$H zl`8}>0iq(Ju`F;TP)h38CZgOkf>-mSwo}I~!_e%iZ58dt?P^y|O?#tG8FeVMfC5tK zf1_vU%lfcE-%?SaVX~5f{8abZX!rg&fp#`}eg6|@#^xonHy^WkU6?=JZ=!f)ThZdTMTW zFoT!G=!5UtYWPmx2&Bqtq`VQdqep=`wda?29X`7b#QxScyb6*a-T^9K>*{v7!0T;8 zwy8umG`w#o*eWx;X+LO2|2-fny&=0B7$E~EskF?0t)}F&9ogNo!FN0k-tn5d46mPQ zx9^TOT0@qmpZ7e0Xg0%0thSS}Q4z(6-Oin1E8zNtR17i?w=U*fl5 zL-^feGue|U`ZRi*VxWuP0EQx(>z79>4opPpa7Z&-cp0AUHN?>=K^l&onZlvgN88jS z6G-Qfd`%u5WFIqOYv-QMReA8@U_52S{VD|2DksExmt)85P}$<1{mE>+l-FrsCNQig z?2q@(Z{%Os0~HA;|E^&W?lDYx$<|E0F5ix5ap~Guw;Ubpph(&@y3`J1h`bz{(Dwa_ zF$H1tTBNXTNbF!K*MrZ?C54|_8?b#{Textv25+8IbkwRIn;VW>psL(|HTy*NQ;K>} zLyCzEg$AxGcSSvX4Kb@twP4EkjYCtYuIDA2 z^O+GT1?`IqyH3&Oft@x8Z{VwG4?@X7JY5zd3z1pUgEE2gp%Oqh`7nd z1XT@?QC)m&_u%uC5_F;3*nFpo@>q zt?^s=X#38@n5z*BH~rV@0cg6Yxx1CORA;SiK6}!R6azWwl#E6Cl~YwHai%}l)RMs^_Q?z|0n7f3+s(=EuY5qcWqgPhs3)cOTTZsX1ui^XdnvqPle&Bv+ zc-v*{v$n)he)?C$j(npQHvip~$(>9Mz67h=3zL-VamY-jj@|DsEif3T?% z)x0ol6w%fkubEy7^rq|kMZ^Qk0e^n)T@<%HGT#hyk_js$0+^T8Q|~_{Qy%{6|DGK7+wOo!* zkcLpI-IuV5ZuUELmDUBp2c@PgJk10YQ1M<+W0u|fu1a;N`WpKF8rUZ|AO3p#K+xTX z%a8%!R7%~&MiTeFz(zbPu73GwQ&OWmr147C$|Os7F7)4Sz=dBSk>d4{FB;WsjgzL|S+H zcqlyq?m9wy3Dx5j1D@?(umel(<2jSYy%#STydDU4;bYIgxwC~dK32Wmd6`~DxC*ZT zIIRjA>=(ru4u-K|u#P5Mv!CXu{FmY#zeU3FccUndM25cd1Ap%8(ERx%Co@OuwI4q> z4RJ_>C#R9|hq>{~?bZgL<@_mpsWtsS$xYd|GHKWC(_Ky_$pX)vwd*PYsCitVx6N5l56muuH(90 z_?PFacN5aDO4==<5fHCz;L>{k$Uf1OHB}cqG!PF_9Uz!!)_oFupg)?L7kYIDl3IhL{%?!%cz9VY0k-A7DQS@z z9I$TN|JFacx34KcVwBfzt{=ZrlEW`QE%y)}%*)1_U(R}~jHn71s*)ZSaN~isu;X;y zz0TbI+bz9XX4rIO9YNy_U$M@D(b($p9%NJnSjSGmCNiB&`<(Psfq^GbU^gaWUG#G2 z&WBM3@mUdtZ4+7Otnk3QjaO}Cw$B^!h#K@b$*O(+K>}2` z-E??Mlia?Ry6Z^uPb>V&aQPi9|6Za%l8z2s>`1uH|FE7<@^-XvFNJh(P_Y_&FYAxu zX32tiQ+0N(jHKkfr>(^()~h#iXIexIN-Sd@2AU4YIxh}L76`YC%Xk624g;uy{~i+FJjMgY32%GA*-H7uyuQ+iea0BdqH?w`g3K(ZLbW&oh!f4>PaqJ4hB zY?QpSN~t=h*s<{dni^VTU1mX^Ji$VSF!fWN6(}mBMPg`@bALjDpAukx$Za9+K|#TU zY`0~&24kjXG`GKUp%aJqHUI#UbT51X9sX1usTqFEnwynSeTVlo06ezL7r32#yh$1~ z@6g=Lmoik3KcK@G(BVs&lq8j+8ChJt*oC^Uk4<AaE#233?WW~A@2VcKU~$mWeVx~OEZ6Bk8g!-$1k!yd z7#ID`(&eTDoM^s3prg3_$%M!M2zG{m@-!#}A&}um>NG#5Wd#tNpN)dTT%>0PENf_P z4CCh|>^gz84Bt=&n30O<*=f*|-Q9?`?Ete&lSIIw@BSE5COiUj7vy01>H_2! z%(g4V6848c0;{v*S8`=kqWNSPJ2oD`k-A3PQmmjf2E_B#{x5z&z-j z9Uu&bKr|}RdG&@OHA5&3f*y}?bsg>9Hq<1J12aMM9x$_u+#bG;^sKRK1C!Y+?9T)f ziGjk{0lTZ}4Q-snfh=I&)XWf2jZ#Hs4^pVawjyDoTaR#0_5iPLK8$$o#U-&oTC!=| z%4^EH}mq+VD3vFOW=wePa$Bcr2lNO6F2u7?nYxVL6()hO01)?(jZ+5_&5%e+bpi(d z6%0P4wAOei?f?WnD40==slUHr1s0^$5&)DJRs8_qd6xw#hIekMDJvELAer9;;LPFM zsX>IKdch#Sr|V8GnYWSwEO$+r0+{ISEj6W; zBfsy6yX&5NmQw)9&~dh)^e1b}-dp`C+?uuG8V z(eaH33^MQf(8mu;$Pge`02E}#tSR#O{C^-m$C3`R7u6MeO3%i!{~xm$mhWQ(H^2Y@ N002ovPDHLkV1i$o;Vb|E diff --git a/_site/assets/img/fortran_logo_grey.png b/_site/assets/img/fortran_logo_grey.png deleted file mode 100644 index 8920ae6cd463082f01b3751ab9842aa53868d8e0..0000000000000000000000000000000000000000 GIT binary patch literal 0 HcmV?d00001 literal 19657 zcmZs?19T=qw=Vp~wr!ge+s+$1nb@{%I}=T8+s?$cZJYDYch0%@{_3@=3;pb>da74f z_1?8BQb|D)0Tve)001CJONjyh#ZUjj4K(DxJMCvu#=i)}87L_NsF}t;`ODuCM;DoT{Pw8c#Q3B8I4Trf0{CS*gE_}0|0y;JpYomrY=Ur9=0}i z&O9Fcr2mEB`Ir7rF%v2Ae?eTV`AIe9m54>{olJ>27}*(_Nd;huiHZ4~Ow4$IViNx& z{x8Q*YT@GIz{AAk?(WX$&cd%J2`t;OuGVV&uVK=S=qBmHe-I z#7v!yoh%((EbZ-x|5LBgPkUDvep1r^H1xl(|LLc#!~br`&iQ{>{o}{vVdTKX!pO|@ z|0m>PY4(4*_y3Uk&y)Wa`!81i-5B4$q2UpAGBt9scT%;tw-NXcBTGALXJaD=)Bo_| zWBPw1{!dT&{!=B7qLZcRKd%2_B*4PQ^#3XQA3Pt^f9U?-=>PZF{#WV0!4-i0*V6xb zQ39~o6Ka|OfDk}hOjy+eR1nD1{6)oM2~w^;`pZ?Wbqk3n0>Ztpy682RPdA4$kZ0 z30RWQdyNxZ2CKbAyr~xY)8sMqW3!SA@j*D-%_oP^Y1r1BxJOg{WaEg+2g~BOl7+u@W&@u)QdotMlrUe$nacE8TjFOzRx7}hSVx2ywZ8oClUdroV zQu8i0m2pi7DF%|1u0z!%AGl6BpkbKG!{R2r)IQ!Q#Ej4zdUg2z!cASFL1j#wpyqQs z+6EnO#~r@n>5eY)sKTKLY}1<<>rN@5JK@zmuF{|=H`F8 z(l{_wX)#cNE6i*U_XFw|o5>87j^&^1XdC(HR63n;eAx}flF_ge~z%r$&L@+UoWROo(m&y!JP}D|Z!9n2LLFhXX zB~Z7(S!u=YhR1m5t?0Zqkysh+tI#VJx@X;#iAve=F#NVSW+yK4lf5NBwrbSi6fBUbCJFA(KlC)B7<_ zD1?#EZTB(Fnt#Q0h}&Y&IfP+4P|TMxNfETQbiV^ZPRmJe)CoV*yGw-A1f87t`6%^e zk9WK51?Ut=Z-T0i{iw!Y{SNmYnNanK{}X*}yz|ykZJdxvT|E75_o@PkHkh#1`>>~H zrSg2+FA$Ge^Mhs5?Z|m%z5qoz@YI-HzV?MDu8NmbS|2L62y-a@5_yryiKu7gvCrcY z+-Ju;ybo~~ntBhJ^^5WT6Z8E=QWynEG~BDnH1coPSz2e_DbO5lV6^y_WNRCQ@d6sG<@rG7L2JQ?+=3hEH9PH zl&|xO)q3P}{na|-8@%J1kDfOIW}yd%^F=dfO)Doq#w#dzGd(>$09_z*bU!gM+Fe*1 zxcsPcI_C$v>f>0hN!^hC=u3=Xg_0m|aw}(0i;7CJU2P1Hqvrq!#spGEDQ zkZGwIQL*CfX7DLr(Y-xJ3ldXK3mkWR>{Fu z=H3eoR5!wZgnr^m!S?5MnBWJS_5p*;wT_v&PDH%PUD#@77Jp*eWNKz>98n|ejhNaF z%+kB3stWGuF!F1-X>z1-IEZJKA#(x+yQ|o+pHagkDm7-O*6ug!v33{y#Ugvz4l(rYICuH#coK1yAo2olBY@MKX!W8{ z{3N`;1eN;sesE!TFWU|qTSO#}CYM~*NA=7c^y@V(W(K^C7oe(#NclevW(T-%Aek6a zj~>-}e)S2NGbd0({@Dzgyz-1wtNhUm2y$^;kq$`e_CKdKs&f~({fWs@*c^<+syTJL}%Ru+dg!+(`dX6a;s=JU& z%L6RnJI|w{XJ~nz^WsyZY7HtlpwXs2$iRMB9m#nG2WA@!-H&Oun=mY&|BV@bu>aV- z+}c_4;h?`1Wostf?e#w1Pd7ri>c-~HgAoOAXVFCu^& z{Xmo3v7BIIK5)#;Z>Sb(dEtkBE~PDyHyS^Zei*%dnzKl7p#c(q*ISPI9`mOVMXHRd)d5;B1wa&rzj2vuanIQ;UQNlRm0UX-wT6=fQS^Mb8x53n%?}+K`wLp1uCCDd4Qo zybky3=tI!yrIl7iMZb96yVkvFH*jQ8cd!~O)lm4v03&+aZBp17-j;q-*(S?7IM9Px ziP%4I#w}pyIH6cRjFJd3=}RaPu`d*vZO~^OYIJ-Ut|)aQO`=|SoY@f`5*~6nK9Dp` z^#}9Tlg#awJguiIv7esG*Rs`*G~XVSo=$;4ioC_A`VZOvFLhf6QzZ@Nd{&|*aM4!oWA@DJS@{z~}|-j{hd>2E$m-hAD!o20vn?pQOu zOl{dS>mA3rvsD_m(8PJ)Sz7@d_@ZEtbe{;d?9LtEqsPpzlC}=kW(*#BtUzCGZz!_j z1xpTGf z&@(`8OrglA#sl>tuaJ)j^pkk9gzs$3zZ0Pobw;%ARx>C0Y_Z`V&tG|QT6E}@BHo!! ze1yZG=b>;YAPIuWNdd|+qJBe*_tD?B-Vdcp)7@5K70z#`v?VPLb{LEH0Tu=l?xikn zQA2wBd$#Yw`67(&^+Fi^dzL}6YVF_IjLCm4#mXMf|Iqmhadq>K``_!k^`$&=_8h={ z9RJy~i-GICe#PW**Ki`ZvvIK-M|m43jFV1K#7^sV>oIS9@Q)9G;OFmo^oxCtr1+yJ zoS1#ODgYbrPw(8AC4(6-s)p>*S`7oW7>VWgxYLKhoQ$o~1~UdcdT zgTxe|DVGu(4}$kdqNw$C_$=A?!PLtBRmEo|SxEXg<4%MbU_06&3!9qZrKcCv1-UCL z3Escpw(!P8^qSmG#lCZ{Nk{IGDg=HT&8c<|Te^6b$_E9+?PgdhPWtV*ocPp(wCS`W z+5tMKJ4Zc8&SuGp1zDE_bbGJj0N?o1vsSe9KPz6C&NL@{v1@y)nQ`_9&(654T*5;S zlV)y~7uKQnDCH2p7*!fE2!mvEBV~1AZpJ)PV&9=pcN2x0Luu>+#q1|THpJk%UWcgI zn8)FXXVDVW#lY8JF4QORk`>hR{3^~uUo$k+1K*^$@9|Ztsg}X>$W>t=x=lMQ7+G)@ z*hHd%#9S7|uO~s}&mu?3V0a5O?Sgpm=jMJ}j#DU|TKo>#7lC(BC;)Nb3<|S$u9w@bH!X8;k2#BtYlz16pY)9i1!{s52G8 zq?4T7FT{tPz}a$C_0!xUlj9Y&lfrQ|`ym@B+NIhPUB#?pwq6k=_BxH1U;FS|e6MW# z_=Kry$0$C7C;kE>Pky~?hpar;yYGr@ZGr4HwZGiG!*setbbZlcC<1RYLQpegJ{Xn zdj#h?z=$iIQ%lJ*>tYztSZjI9KEBtMWtw+{v4tf=JmA=DvZ-jdL&#d^D-gdWmd_@?3@KELv&;l}X}N6YY=>;v(hZfNUGtW4ir1hT&Q!@%KQp-O%4 zr3qlH6%4U7l}|JT(hI#lcxD(WPahoU!i@YXTp>SU2~mk^fG`t!i{W zSx5>b`8(auNR70gZIi=WlC}g(zk=n~VUY~+OArz)*a+~MOnGBCNQzI@=Pa_jdV(x+ z-xyrIK>Paq(B_YODOU<@35p5I+z0WYQ=dD@`~)atRc`19xQUmH@zT=~?+h3|^DTS$ zed})g)6dsU81V0WEZ@@DB-exgHk`*j!yLf|TL@uN>_uei60=>F?3ckOrXuZ5Y}BgD z10EKCdU@f}+TMP7=1d0##(+%Y;g_yKx7>oL2aH zd%TaYPyy@c{-ZZH!{2{?vP702*#=DPa82?cX=^R=i=h+6(7eEsg=1`1-WAp+%B^(S znu~XAwAPa5H9NZDjv<9{5)3G`HJfL3TM&s6mP~R4%CH7WX?#%z*|dKzpzg$b8F_UK z>@}Kxoiph*73w+>0%m-OUZUma&oWN%orZ4v-Cu`C%M$!!Fq_^ zo{tv%-1A17z%VUNY6jbS;2gfY5cjpZ+ndA>T5I|HkxS>66NPgT&VaJGCy1ycwnsA? zIH%7AlKsPI^@`ngZ^ekdR;xxc2yTEvgDYCTvL|9|HTq!2*DVsxjy$k$>b$|duma-j zL`$XJ%x-LU<$Iq=0lYYrXas-9t%_zH)<-V?Ya}q9WtE3T%uz;ZQpWI$G(lY`8`P^3 zbbT$jC(O;A&*ZScJby1y;X!wZ3XGfCXtx6YW{>|bnwrA^)ES1H7ruC;RTVFTI98*g=-T|*eVFoVP(!$(NV`5l8d90%T%6N!Nk+zy{0?-fs z5Oymt;$33wH%Y(XhW?vHULocT7&zQqHO+fH>$|m4cl-_K;bBRoB~ju9DxurIFdus> z)(j^Lse-xQ|K`ee$9XDj1G`|O8c&$p(d#?HSXyuC@K zTRGqsb>HSmGE(Nt3#a{kYJCOzrgaZSrCf2s{!I?MUHCUl9wCE~AdG=QJXn|HEDB#p zJk*@6pb}9nzstjvv+EK}C1S>4rG6Y>1(G!on`UMzV1$Bn?%7zgAPUX3%3ek~w)~7u zccw82GelQJAo@Uv2sf`ASf`q-u*D^bMUoSTN*r^`aLML)P;hMQ!4~$R!gWS0C;@D2 zrCYD2s#)v4U;@?IR4U*6(mRH>>{oNQwVYFyp+p)7Av7VLghlrEQyNuVmk@E_d36** zrZ9p>PiJw3>Aqf>mO4R>9osyOLM#;Wo_E}o=Icu8#@K)qVE#3{{yJ!pHpchfIM3-&S3WTa!(y3;9B_5@-C}JDD^F5X#QL+Xf z(Ct&Kh;Ng5avWAOP8+}#Oxw$q$c zAQGjztqRnSg9vPPYQ3Jnvzq0vbQCk)gA5%8z0Xm4MC)vg7vUZ?=<{Ka2AihXN+4sV zmVteQ;7x!Jd>476yfG&Vm4m@E60B@!IezG#2+cRqEe})vH;7bYaE}IFEaG#Sf$!QXnfn7BuXJ=>o%0hk%pdJ zp3WG`5>t{CFN%DrQeGOg@B>&Y2y12p)3P}{jQh}b$$#^@M)c<+Frx)$*2V zR)4hW${fg#f0~$Vyx_OcQ%9>oTPho#7K_{ZdFw#-v5q5co@fc8g7N{|-~!71z6%mR zXBr;EOS8|;#p$e6){s3JoCNG%2G1RNyi_F*JUcVqfIZ?C-4*K*kc-_dGv9APoJOKoyJjnSmor`+OY6=pQ zy1R%XsAWjKl0qef9X**QjXD~Z*Mkdjm^66&(FFy2O-3QygcW>#4VSMKS_);pQOv@0 z3M#HHq6kg(Ata3UXSN=cao!DYXfLIN1s|AY>9QFRyl4~sa6<`b-|gkqafzR45eF8= z;FGC6rBd@)H;kgi+(Fv@wfP@QbmW_%O%6>~8)cRQ02((|PBRun>Qchkr|S{zpDpNK z-%s6~t2QoU2=7+;{IMSt})OJjQ zS~2^uP%W!u>Z2971q-(EL8ZscQm6aX;VTb62OruO9$ful?_JPUJa2P8bKrWq=v}pC z304Q^hIjRH_TgL5g;gVBg9;^bo8yn#JMSs8K18XxA*Y{6=ac#)aoE@^a(pr&^yD0S zsjw6p@{rdd2dPCxjOVR|suqRCM-d@81Tm&A9#Ui>%@3AG-!vB;|GwgG83s~oB_}O` ztf@gBi~-KC>&$2a%2IL_%?y!Ft9207{7^+@kM9t)rb`BLtt6;OF57^6U41TY6bG1G zhtS7m3;84Pp9jn3_M#!tYFWj=xgfSA19OvZhf@0i6hX6o(ckYQ#RaSRCvsd6SpIbj zh<(^;`dj&^2B;c6uJ`9NI6eLQ*jgQDVILepcrq8QdW|0i&XzEW_BLBcRj<8)@G1U~ zE4dELr9b+EMP?g|?OURI?W7N>U3GUQy>z7u0`~5k+POwTzOfUGFPzGiTh3D=4lFH22az5?^tEVAa76ttU;w$V!x zH$py)Ma3-Ng)W0rTx6*G1ndi2P%ha-zU`wXRL|Xf7rP~oWcT6W!RmA%904=mF5Z~S zHh!XqLb}NgFeF?!HdRC24uI^*icnu8F^||upwVe_f`%#%Yp|*#x{Oy1(uAmpe`HNA zV}nJ1bQZ(l8+G{WN?Ha+h&q<;P>WLZj&MVD;BaPYbSJIuPz7R^E3lEKtDHt7Wi(1R zgO+~YiW;lcFBWz@36o~(6$+X&;lKr0QC@wIF<|?=^E--nY|~UkC0$ubk7izT$|AuT zaocqc-0eQkqGR$#><{UuPaG>1W2HC@hBS(uYfn|Di>qaD#Uu+B;n7!#ugzPqw{f3rxahZCI{Z@DvRwS1)B}>ePnn2$+;dhA)D~A%+ zV8rxR14&I#komS80WTbbiVa3&%yG5Qy*XA4Te3IilIH@)e)J4z=_f8 zKjK-AX8cO}%zSBv#}2!gqan@ALXFqjj`Q!=gtX2)bk5QQGHUHUZbb-aDzMH<@y4cg z7*~6JjwCty*+&?g8fErNla6hmBiMxEkzsMb7S2WN^F$HMJ{3D?Lr3e_pTyQ4CR9*d zZLS(QgQ+6CF-qVcrX8jGU2Axfe@g9v*@Tt6{=Qduf<5tdanf5mjG*9nyiNNPUW3Oe zRMNhWTv!OEw$#b;vD@NP>7zme`C~;`p;C&RfKLwa+>a{9ND!yv644f42A(R?2vG|I z4P091DQ?ISs+Iuca_+cPJeumn}O&Nt*gkm$?(_O@(2e zSj>7qck7PB?dDEYJbnR8H4_EAF*S~s?7+g!{PI;=6^W7ofHeuS5Pqs-$#T@%hqt$| z;w&NXF^=yY>ud%NnlD-_G+J?;p2h0<4_`~yGMubbK4a?`1y7t7lOcB;k#)R)9Dj3E z=jmds$$8P%9z1BxRsI%h`XYY3&>QA5TW}wrQnm}`>uvxf zdvRThz2&PDhpwE2fYvZQ1&6EjCzRtK82>eAgpe0`Jn7X;S*zF&&}qX_-;x~W)wPj0 z3jhfsO3m09lq6Mw=|p{v6{!YIrmc0s8FlN7Hds_4Gc{f&e6$jkIMS{;MY-}XIT~_A z8_H}bYIWA9e*D)j^`tC$P97qJNKRPGa5!#e@B5U=LLL)^L=(%h9dbX$(jooZAiOd# z+_qL8&=INDM9=fYdmKiVQ;@75_(<9#bVmSevA=Y!ukgqmchs(>(v}I4V$gI{{JDlC zP=LF zqRTV%ty7gY?bktB;|*DxOU=2rLa2Bj!kVHbVOOM+udG#j7x7Uv4(V^8@&wrlT&uzFh}k*KJXKJ zobO1G7p(*`PJ5X2bh+j4w=Yr83$tP({EFg>b98AujaWmO02hdq*Ya4j@?!{Mc=0~{#+u>`nP(WDPcdrrU_Az*1c4f`v6o&+l zO1YJmh5J3#iV+nmH07k1l74~O z(Wg!m1YS>9w_?YAbM1~TgeiL<%9Vbr=Eq87DY6n%+F*|Ms=)esr}+zo|Ab^$O)z&+ z(=jJ|T~BZgnwzv$Q;;#CHcUTTLBI#;dl=|;x}oW>fbC8-d?bC4vDeR%n?_GyBNBB= z^T`oDzG)?_VrjhG?_pG05n4`|BYumPb!;#!7y;_AAuPDP{LX?HRahEo%n+?U?)zzA z_ZbuY@^)o>1%>FS<(0mc{VZuFLpAZtGA$-tx)IBi>ABQps<`twPFFW5?Nir2#ZREf zfrB>%lZIL9cBAaXkB*{E=--bOJ=;mypJh8O7>0ZovylQE)xtqdTOlzMBXOKu9;;4{ zQe9VfNQ4f@?9++%pYr`~{x|PBCx<1mML1chQr@|^YR&bVODD>|tX-&WeeNI~H)cZc zgarh6%y?zQwjjcX7R}g9Uqf#;+j$sp*Vur$upD-1*bF#nl zqs!AcGRGXwgTr@8&AldWw8!BAk7>9LKTsub@*Hgc+6ypy&kRn6I?s92sqN(cl9f18 zcaRMLnPRnUsZ4l{#l!4KQZ9sO3Xp&c9U|ofNeQJ!jj8`71Iz0Xh&G1wZa7+5%mjmhv#<+#&r<} ze)QS5^*r6I7Tm?+nF&&U#j>zzx1DuX0yC}Ec$^gXg;N1()7eZ(WqR74Vckha=l#gj z!sgE^+Q2%IhP4c;p694DI4o<~+L1A(4U#=d!!}1F{y{tK&d3uUAJF^0>H{Uq_}}&M z_ZrCiWf)CyJ%69$2`|*`S^rr(yS!g-_W&=_(#LAzH(S<`GNH6&o%CoDLx7B|?!upr z!Lx*` z$=gD~1KPr9uDh@&_ck@E8I(kwxghPHXSqw>EC*Z4OIqIC67RWu!KTBglG|&zE{sm` z{N)s5Tp7{UGO7BBR}vcs2K`Llr3jzX>!%!;bk?A5QsN?Bcl{5kub3jjHj>yPLToir zNp}8|*|KPIb~yrJiB_Fz+;uLL?hW?`Mge$}rULpN*h6wEc#Ms(hU|b86=tW-Jf6~5 zTu^$pVh-^64sw>H4me;(cT#0@hcENZ&%ppKWlkPinxer46^R)evJ;_hJUr{zC*D1Y z5n2uYb?LUE*kAlu>p&o$Sk2PN>30Z@N^NMda*wQcsB*8Q@Sc-4YqQwtJ)QFk0+`8# z-OW_zE3=``>}aqo?zkK_01UenTMi+hG_k;8Eu{Zmike&yPgKhvJ!$ChR_vqZoM_93 z009hN1+Rt>B78IV-?HAn56~P^HwZ2Txn&2Uvvu>JzPs!T`|6&({<@N(VaUXpo^$3X zDf#sq3`zkFh3dX?JuFw&Lv^MU-JK%A8+ z{jU;LiblP!xHIVuBmpiK^_D%Z9`nM)slvcG=(AtA(@@qr;&;5>ZZ}@gEIrq7j>s!u z`(+<$T)4VFvv_w8ytTP`VWhTvHY1_E&@9iWDWn9SYX?!tJ~6?AFU32C?yxW!Qw?o5g$ z8;^%J>pQS|E}xu;4$BYk{LTF3b9~r*W_o+)aIRTe1B0GG+;e`|w&}C^pXGX_<*RPa z3P;lS54#w$>e8m%zug~|V;Vf@jw^|3+VGvMx#%)yp<_l2IIO7~|l5l{p+lrReCuu+fDSnW&`{@q6MTYha1|ym-C7J!e-?Cqn6z|NVL9 z84;!N0#8l8)P5}v!bpJH@M4L#E?#Q8_DAf2iskAElh&M>&anD|Jv!_)xLdB@rH21m z0YNrV>C9a-OUpO5w1)W?a*igAhyWr*^WOP(wdAG{DP&+?cM;<6A&-2iI0cG;ddC3$ zZe7}3JzAc>bYrZ6yD7A(CJYT@I;f=uFjZe^qgDCwlaOhf=@sSlb&j7N3ZRgnO1-91 z5R~Y^kW@Zu%&xrfyGtt11R+u@F3D%gm=KVAHX1dY03b9)AwX-f>+Uesd z5k)<-0q#l2la5VES&ILypq)fyrP(A_2#%*5WbP_20QpINC zAu)vY6*|*6|9mlrp;hB_AZ8%?xzg*;H?J_5U|CNq_N#@=+NHnMQUE1k$TG^w6IJtM z==91*8{7$tYHDx^J=y959A+ijXtJ74jAKWx|6Jc7YDD8#P;;wT{HNA)Zc&)$EOi7l zQXGHGz!>C+(E*n4LVo=krdpjWQg<(&n%7JlMo@uaFq^&$n$Xi0pvXH%iv`Ch_B?^DLa4p-V+@yw zi~#M@BnqAEW?9NsK#~P;x#u5^$p5&_A3RPSq`oOCCjFW1uDyBi2Ll4(HUh(RQ#3~n za3Or-9>SiMgLTrT{l^te!V$m5R5&k*+K0-XkUy+aalX6`31|B=nbCCiv;ODOL`>;# zQfFNRP@cS7{U}EcA`d~Q1Zx8p2IFiB_)wWO=u3OYLT;b37*3Z0YCJgUu}pOhYZycd zS2>@iYuLa&@brGTi5l- zrSYWl)S{MZhN%K~)Jptt2)>l(BI!cEcnQfpz9)-Jo2W&FIQ5i%1#yIElBc+^13fN< zy`RMl2~g%J5s3`DlOe*2mgQ6r?%mk=xo8zTBlIkQdr$*;OG`^`p`@V#K#~%$v{#cX z+vUE!0seUKBwl;W_hXSuTgF>7valeTfQ+2uJ0^EwWE#Y|G3~_kM!qT5)Puodr_`V9 zC@^c;X*yw8LlUHb6isDa^y*K8exWLM7;QK+f_g=+!Yl z3}3~%@{?L~?~J6+)ldC32AByy?}SfjnR@<%`OJD?3XrCY1+z&{7oz{~zsT04d315D z1s^kJoTj=hjJ(gi1;dK$6}%_Wx>r;>r(^giq#uv#SGNIT)ef#{05wt4dc$c2c349W zS@O)`-k|1})uR2@$e`XF)p+xcndoTNYceV?RJ0;{zLK{y$y{HEDZ)b8iup9(G|y3i ze&I4j^kb5QmV*uuEcGf~ODN?pYklazMC=s^=Z!A1U>aH4s*CrF`nqU`(J!abdNz0! zq-egJI3M^2B=;@q87eY5C7u%m&rs0ZLKasY`Kjd^@ZjK0P~7ls2bT}f%&d}_V0_M3NkP!A4?tYT(85)_187AAGSp>m!&Nb3i9l}2e?y6 zPk4-iPN*qoyce9w#sRBUw+egIr5Z;bq!(F7MVaA%;EcxpMXn6KIF>nN%AV?09w<{O(4IDEdj&A_{{bqOI!B|^3;%wS*Y!`oY#xt(el zv4E(Sr%g7R>skfjo5glwKERf}{>gwHp7vu;d0xv9qI&Zdb+IZ&ylEcA;b-{073^ay zY{C`&9=w3mw=&!LN($clFA;pz9LUn9^OE4pwe_qa(3#AHhc`$1$V;vD0HV4A`VczN z{*mU!K()9Fx$0rBwcuYRpObiqtC(+*Bd%eWSK@=g5M_x(efLn2CU{k){KqGfzy;Zi ztom8VMwh!V!qAH*7?HQ~QiTKH+(Ej6A{H%go_;T<^Dba?F7^&sy_CR8xz%CQHGkOw z^;~1y6*a6$=EO0wkXtx|AI)+@(irrlV~za&&weyWK_-*(f@b~kTHg=?QtHZnEU{X% zRJO)zyCOi*=LArV$31lDv%Oc%kKwUcVwLOWBzYaMuQ7nF&bdio!EbKTh`bC?g5&)Olbo}5D0~HBdkncKt&yFJNnzf z9)jdrNNsx{(u$~p40~O(Kiq~ezwWsI-8Q2G2~^ZO*ucf%R9GRXZllhGv^+4Z1)BjQ zx))&f3E_#Y2p!wilp2X_ncw0@YE~zLdSK`c_dT?xf*ppa%(*y>DNE?JTFmT-ej<9* zs*EOl-jqd^UU$z(1VY7p2$|*uw)scsT+5B-_s%UYLe$P3;4Taq)>G(Ar>j8hjuZx&lom=R^?oy+#ST zAo_G5#8c-P6dVX9^%xG+!bzjb4O><@iC@J)%xlgktJzukG_YeOcOpw$m zYjehYzW9~4{fh~UK++?_LLtIm5N+HFZ3Cj4tQYTyAyC`i1A;O7I3K%>SH}0N>c3DZ zX-Zhc!30L)9u52JgF#_h6qIcTWZ?4~!L;jAo~e6>96JuiQNuj-;Xey41`oo@!~3^K zWDBKK@9hicoUpQk%2b-GLcxw_+^)73~b zIPp;P@MyHClhbA5dUx4D!{xdyz+G1;)13Wxe^I@;`h8~{7Syn)c)&avu-=9XuuIOo zDDvPd)$c< z+?&RBr1r7&@>zl%3LZi&`M%z(^i8GVPE*Tk{Fp%GeuRT`2i^Z0GSYAfV5K5go zrq`TEkojK5hF4Mo>c&b?psO!dH3wR_W3+FmQYu z{k3(!p+bCCuV{BPE!r?~d-gkXH2Hg()4Fv26d#u=>%u;}Enjkwc`-5~^ry;c>jx(J z*b}-oQ1Gmkd~5t9Ha4uLnau7F`L{>As&)m(bvW9&Ud))MQJk@7USmMLt9Z)_u>T8! z`59{s2LzZkRr-R=dxQDdvFu9N>1PpVYD0}z|0Sd_9aKo9g6(1*x4C4e3hlBps!xBgo)D$ zIsz#r*kk@O+=~!B<~@G258k?84~6uik7j;3Et$0hnH0%u1wB**vt|rJtCt$?D z$|K=wFe>{g;I4Bkj{N#Im8K|?Hkr%cRY^>2bLy>xAfzxXQWJc@UpRgum38Wj9j=FY z1*J;^dH>D%=fMEwYR10ps3x9;LSXIVS^ZcT6~CFvApO0*EbtnW=!8tJhY<~Nj-w8iOCS^j2OzjuF4jP` zAsE(V4H&mP=(5E>i3I=T_;<*tNDK5pAX@E4a#!b@CL;5uPjYB5_ey}8;g1nSYHDYe z_t|D8zmmbPhqKgiCxZX-!S7Ld7Z`<|hPJ5(lj|lpYyHXpfjLAp>a@Umt3Kch!j+^i z97u)rv4FpeT88>)4AmJVPnAl6JYgB(&ghx__fGDeg@hNrNe27JGVWAw=iPGWwj6JC zIN`PtQaq$LdTi<_F%&qXiF4yzb|b-w8~)y{2MIJHZ|JiUa$Oli2 zk8=_+HBtZNt4v1EwJXPgcY-XTZ#F&zSAAPkr;Rbr24-lE*kRjoq1xGrX0zh_h3gN@ zJotR&&xL-F3oH3hn##7H4DPEaySP0&04%q85+1IYx*5?eq@Xe03ialyhh1rLBLCtS zE4JzFZj3Y7Qno+}_XrmI(bgMF?dlzER`mRshDUwMKn&*X_3bF@8A z@;j;F$^A~_#w^YYN)1#&$UI?##N>CAlauI_R8+hrw&WxY>Jcc#%$`It4$^&P*1W2P zNLQ_RXJHHarz^Y7fcEZQwdR+llrrQ4s1PDt)T4TmGyn32fmA!>01v`gj+XRH$+Mc zBRJ?wph!lbhK|R|!D{EMthH%6)WN8B-;zYUM&e4?Uto*^I1zBie6j^zp(hOSxV5in z*QecY8Qr(prPvG&-B_B(#*Ce6fBTHkp*8diEjX{yzlysS*ch%I7Q>DfON;WY-9x-# zl@#ZIDxju#NzgHCpP@8|x2eFIMRL(3jtz6U|FBw`LM@rn=Ts*Oo8I`dL1_{JBJ3AR z`N8}`jf{BTX!77dN2DJatknC)AXwc@k2Kj~)*^=(bYfi47jcH)1m3J!K0-*&oc+`% z&Mlok9K&Qp_yKIomlJrR13;JMH5dA!QU_zVZ9c>GO;CxJI1@Xv$QF+2JT;KswO;K%cm;unR= z$x%uS{07@YL3fbR`6M2Q2$pxEN5v7?c%o#eggs4!t36%YLU_Qs+ihlq-!Hh4V?GYI zjL;+=sMF0uVnbOd{)~c?83<3C_2v9Tc#&5&SP-?T2^0(~+97#EU+sTqR=WAIqz0X^ z?bumJMB(MaO*aCk_&1p6O`s0F*6s-3?EnBDFK}i z;$hBy22{9vI21bP(RQr&j}jnhL$vDtCAxSzW{bO;^+nd( zA^7I3_QjhliUSE$%gfI5tDwNmQ!TFi-54gO-Sq^fcB_;k2w|X+*C+8hagM;%F`$4< zKvhWxEj=FcFra6u)nDH~ewENTe;q35ax&y~ekR(D^mQ7zaEekInzo9nrLdVe3OT4q zSa~ow7YTM#pZ6NPA@EL~9u{QI3$72PQi&_2OxOpvYG9amZ0aEymPRVLfxA9GJa5iW z8PR;+-VlQ1ZTEC|2wiHSo~}c7erfntyQi+fb)Di*OK?N>F?)mz zy#c0=!AP|%J;eb5pRatVF1z!>o%)1D54>@V$Ly_07Z+*i%qI(~-p{NR(#~6X+>22% zIgUvvHT8Hhdr7&p_K!^+2)>^i~kg>%dUrq(T+qbOG@}zu5ShHyy2SNyY9s7=x0%nMNrfdoR>G@ z&!J^G4qZRMuO2SyHN@Ls|0_IHKaQ3LXnO0^#91Tlx9eWPEj>)MgJ zW+x?Sa`_;h97JsUuL+q@dIO};)Hh*3=O)xHLp^}fRCY1p;l`=<9NZ1vTUv(>)|-FLm7<%TCG;) z*!uTA@ORJt=*!P@&`G?pMYCHrDtHt$b8j%P*)ZVaP*WGfpWnS<_U@0rRti^kbw)K$1_K5I$zXsM?*dL@J-FqFEss`S z=^lG!v3;4E<4GQFPD>k%uD?zL3jWiwnln9eWwp$+!N7*VfHX>y?=T2@S7mOlp=@0h zzV8`&s^2=r{r7)2;Hs6|{_os3FL>FDw!vujYG~m!nyr~u=V7h}0|o;_U;yVh;%H(I zHtG-JG}aGmxCHQuEn*vs#y=)|r!`S>XO#@A^2lAG{WT zJXJ0i^%#4g!Mx7PTnz>`IR?lt%@T}aDi<&NTP&kQ57369CL-+54uZTy1*aGjqumc>9|eYM+C#f(7p>J_>`qTyD;ft=v&6Z_*kJ zq<{fV_4?FVJ;(Jt&#|!U@iDx7FSbzL&hp93d#hE+A927FJ9AawjX@s{f8~|aTgpxG z4w&cPSt=CHAxAfwa=5Kkb4u{oVTc1UCJ%#w5imef4?x&tXb)O8rl@QS%RL{3So@>K z($cLr|M`8-GXE&Qj8I-j(xe#52C(pQs5Wt5b=8|ng{6tN!57clu@~eGFsM;2x9BDb z0JOl?Hrx!sHID=*DVRDcZXOH#?TPqClfKYN!t{2g%^deOT2n%v*inOavxO7Cjbv8LFIEvx7J&i&hGof@3& zHmsd+rF%XMZ7+sgej!l(9B}U`RN2`>GQia@-2Q^$;pkG{%O+|wJR65W)sugfa=-kJ zulNq%BFKo`GO7tV#(-{PDNZR>Be1G_zFU5)@7TutQR+$`%J5VRkH}zPiU@?ru<(0$ z{0=DPL0rFz488_O%m4nJL(aG6=s+YAI99f*cmW?`X-MTr(e2y35U+A3zmrF$_C$vL z?#rjoXt~yNT}PY)C*RM5h&~7H@*E)h`%$A)@!JMwFH$W+JGJ$6#ph&R&G?AP&VWC8 zE8AJ#;*o)D-i;8{*UrD)afr9Fvq0SL5jr#J7OkDWdj{R#uF7_#7ZNei95kj@FprM1 zD!%@}YxJW`AAJ#xsP21xRrTgy)j?}K@Jjwv_?GQ2Ur0L8jLPo}vh9Ij4)egg4cs2Z zClcU1K7R|1{}|k+f75sEM?A;+&kuZP?nx$N+Gvo%33j6cI1UO7uC>Q#l+^DvLQ*fd zUxC1!eJM|j0F%$ppKBjJd^lLyBSzC#rl*U?ceJ)SEo%oF;WRkoKLaD3Ga$N8$GpPn zVDVEhAUXw=JsFL6653`9Mo8mm{W9_?qQTJ@=#D@W0!!$J9(D@LP{`ZJ3-zqOtB8^4 ztH`4r12?Phbw0SFjE;OFpOUy$JkW^;`4s+Hbsq&Hl5F`lyu)Sr9TJfVBWb&p8~Kb| zg@2-4GbrpcFi_!C1k4^GLJgTN;_GqTA4BFx(B_Bnd_4IH?0uDrZG|fP zuqqCh;gw1YW94Iw@zz){Zu!oH9rzRQ!8QQ{#{`tGahT}Fp^1%yY{o$+W6;gYAUSjZ zqJ*h8o?KDHa}nJ#H?b5j5byvWXv4xe7WCl;~RJ79eXEF&xo9KAEN?>RY6MM2%Q}`4Gat^9M)}B{Jg#R|6i3wgk@NTthvbuSyzS;p&Fb&_K%?DqyK2u*`Us&%kMk4 zPSvfdd#mpIoOAE5hUvO>?|FRZ_nqJU&htCJ^US9|wfvFhM}!c|r=ME;41Iq{|M%}b zM1NQAy!1!(b?CD{^{F+{=YN0t^*?`^?i~J=r=Gna#E(44|D6}V^28VD<~^T3{q&Rf z{OjVg#dU0Vb+zB=xcwycOeZ9< z3tO^~PP^T1tPaR4MC-tH-Ge9@Ha1Q!E&t~)+=_aR`#>NL0?Q}1mt5Do6BU-~U_%Ix z{tMA1vhVEdaGf;HNEktCemkxYNIU@R?j*1b=*{c*P2Haihu=V;2n2rb&GU^gOHIaS zfsGH>+ifB_5lTDBwUJsjb6jfX&}Z`P2m%*TEsDzn#s%q3&G|!$efqzkd7?~1j+3;&u0(( zW-V7yq;}}dw5TjIh@4eTh+h>16v5eYzq++`hX|Paz*_F4<~NbD%ylI5zrX(eb80O> zRVpINQ7i(A=t1t}m1AxM_ZNz^7V1pyyp)1;>VZIz*m;he=R#^4-Cj^5+jX?m^{9d< zWl;zyatC>oB`-PElqCV~CxFmd5JcR%BcKc+^N9JB6^~4ong!s2F(p)1VGth()Exn~ z+KN|cu}Dp7)xig$(?XAUKp-3epV%kKU|t)p@dytYem7O~o8KfnAO=E*gNnOAAPWM_ zD<*W>rg&mYt(pcPbQZNCE)bZHK-#8wB2t6U^A&**#USw7Up+{!27JE&#pGaqs%c0b zo8ahAn_mGSVKot8V!N%@qU%NP0S}fuR{xsUcB=&@!N|A<0zjY?1RN%`zsF*Jez8d1 zCD%fn6#CTj0YwNPkT(LvyTOhx-y6%k^yiYAo87!Y9E6?+C7uI;;t*i|aci0RI4_r( zeQI9Y&0ZZip_|v&Q_Y{v69CVF01$|efb3t(?r`*e?U|N(bJKT21VYCL9U*~0(Fm|3 zl395~l3ERpq1inPK0E^g z$S3Q*79cj}2nYnqKtK+l&6w^AB{(d08LB}ZKp-0ez1~+t``KY5;e4hu?{ zX3G|_fdCLF0)a=!FFEhaR7+vjg38O^Q=m+Ogx|G9z@hpfPhx%h$hR8b^M2((6dDpIrCg%lmuQ9`%^ z0zg0~0;9QUNos18bC;s8V<=B249FV@Q~?3MbL}2*=bFnS|Evsr8C9WxC<73vEdqmn zwIuc1M~=wv+Jb?C1A!_a(DDl*$=qz-&@v`p1sqWZAYcjtYT*f!nkKs9IU6=bc$P!C zKQ&1v$YKftzxiu#{$ah>0u0u+I=mW1&cS2A%#_LrIen^Uhg486YqNfh65DOqb38ve-wh1KyX}Z@1eE;#RR)<(>M+g*Zgc)}qf0^86fw zEfM7og`dzUp{jW5+mB$+Up@zQL9|8!_j)%a@j~|ndP1yFt1Rd{B8Ug4A~zCK3KQ&A z_^9tuhV!q6Ns*@kvAOBbw5Y+^HpSl^jOnoKEVpu7(;@v( z+fvqqZc!qOMK#7*Z?^-3g)Lr7YeUP0^;Y=`Pr9Hr6`ouy#bn>6R;8&#=Y#2Z?T2nI zF*n#!7xVe%5B$XEN>~e!6~yHe+e@qrSy{**>&Oj~C-_8g(K4FolH6G_D5e7Bm+HVt z7r$(WFI+A-w=n(L8>4lU9}p>0DvsbOgefZupAvZC?0RT+E;~x|h}`~Ln764KWgW@i z(;^?h6e@g$ZbrSdF7KRo{Fku*0_Lt(l*hmd!I7vawIuZ{gj8j6$$t!ouTU9z^E56%c$cc`z|^%Ha$;Od6>{lY*XY79S}1` zxRT{y9r1r6G<(4J2Y*YJ!Nly0sjMb~BP)z-hBL8+8CZEHBBfU*^#bN*xEvGFD~|Tu z&8Vo_VTcxh```XkH#$&>PlD5RC1z`UR{jf^x=LiVc|62;feRE6q>cgZpu!l{438mp z?SkCAexLM(%`+QyCN@Z&pz24RF`6KW%t0p?k7Q1;f(iI9;rbFAq)t$&n>X}$a~~6N z@z3u2VhL*j#`3iMha$OLMQM3i5{mCME}VVk-Gq^98+e5<4c&&7eV9!)krL(YupED(FaAZd~kD)1^P(f;w zLc(ad1=spU$*mOSB~-^|I7nSy{mLUJ<}@sI3MA_^*a%W5tRSmO!j$5;qM2_QDeS z`TQ@v_UGwoX=dkauLif1lnQ}4UB_hsw)G;yFnM=kD!(_+cs+sQ2IhoyC`5 z{#vPJ>b&FK)w@@xI1Pf-39$_xg^@67rGqn})B5qH^_-;+T5*fOanAFx7lyf!&8Lc( z(x?9GwOc2II3`Z7ojR9K$&iXR1TyWWXz3E$KQcsD?nUKm3c-siAJQ!e0eN^=NqHfg z*$9Btv+=>xm(S$CbxhRDPa&8q)v$1E*yl1Bj$zQw&8Bo_FRM1Hq<%`WUPzxZ3|Q(Kx!Mb zWPyyCc5GQtKAS`Yscq7hfwC%ZC^)v$9OZ!2Np;am8ln2(*$Dy7XIVQ?CcMNtI{eSC zJy`x)fW%@7G{sY3hA2}A*zJU%YGVVi+EW!2HxeV@C5~ZKgsP1VfYe4+FH41KWm{LR zn^XgDF4nD%i>fUkbrdqVKNkTWFyo^q2WzS4hBq|;d2_LMY#;3t zTsZs6yIh8>8$5JwC7sj(NIi)Ne$PdKy>o7CoLs6#U(|VgZh>P2&^_1}6w%^SJRbha z-#%@{T7V$lmAdwu;PNDlR7dg{3r4rQNL`C$o>II~X?ne{@<@8J_@n5#URg}=Tya2R zF%VEoMPmfDE{MCcb4z4tPkTZrXAIg4f9BGai(s~PHP|6Q-?{S`OFEd-vc7X2MBNxh z28GIS4N_+Suk5HKjS7rD+3m&G&#mJfI8qzEu2(4KGDYA#9P61jSq9`)+ z5C_dY1Ojh(8TeDv+JoP50W>S2ot&2>n-f>?;p^0QIBm0Va5 zykx+U9S|rQ0g$?AgpocFC>a5ex@5qST_^&Ta?l-G!V+(S)FpzAtbjln2!PaOpo~0# zK#2%|)FpzAtbjln2!PaOpo~0#K#2%o$5x48=b06|AL@41*2?gd*`o=c>9f1KCzo3H zddHn+^G2WJ4ZN#hfGQk1tMAr^)DM0A{{PXm7NGD7!bfXxCiAvg%1xNVotWNGE_R(n zA3o}G+?j&E)pHmQ7xp1g8-m-XnoxemOjZ8v3Yb{pA^VB4gw%`9F!17BEZDv`Em9|t{{2y$zT0aRo4QjGTQt-RFuty zfb2j32#gQ_sYh7gDh2|+<#y?8E;Pwwz@;b1nM+qLg4ueow?5awx>bMmX@=5ZsY?d% zBBFxS5y0SfGy-h0`6-#~h3HUtq6-0#S{L#a$d|W*RiGG^D*{MulS(~vgni+emmcMX z>A|6KbEK=cBp`LY^`E-*PJi(#N9GOPsS`oOLJ$C{3xTyhiOQ4ivlJH%_(}AB=4+pL zIJdO`AowJ_bAGSTiSKiQ)avmH`q;+l8>BW)C3Xq4PJL{W7|n5m)CN);q>Oo@nAS=d zO>?<kM82We2Gff@-R@OjrzKf^Tm6gKT+Ndt(ZvSrCv~vjQrSy_cmFu8a(8p9RD5xFGd7 z9)n-^9{%I^gg7Qnubny<8UQyV5XfVM{=fg}GoOq|9=8)B0D>n348f-nK=))C6P9}mEG3RVZ zO#rD4QH0H64365gxd@e#9i*<5I#C!PAOuK_T95|UtaceFBM%@@A_5?FiC`luAW#MZAaxli*B}p!nwg_ykUF6* z@>m|3FiWF@)PnTY>)iK!b zzxDhRs31u+-)bfI5RfGO7-9GK_qEFqLretGhd^KU&9GT^wg$KlOD38ZmT9-t0XZDf z8wfsIb+voSbrqI6rrI~%mJxkfez6RkhG~Dn#Dp$&u!n!^=l-qiwE(GwH8dg!9$PW` zo8co-O_F6K6|T%c0HmIy2X5N1m87X9W177z%f`mZB}{Y8QC>|SgVZw=uSnBzy}=&q z8G%cFw6%5Z4ri%kEIE5*XD|XF^&I8!9I*+5Wg%ixKih@=LV&6JEmVq-8o-nJvf15g zEh?u8A;GlY;%2x@GQwJGSA|gmz?blZIut>+$wII1?8qkWL=dBXx}JB3iR})Skz%US zDD`L&Mq26*4!u)*axlbZ$~)C4DO#Am5U?4m&>JvWnIqoJZfZ#(VH0pzp!`3ViVkdvF*Qzr~#u zD*G;xe5`1m5G&+iMd?1chr83Et)CQnJc5ur$7UFVvE=bX4+6d3ac5Cha#FBOpN)-; zrDn4^*8i0ikqa?V8D+&BSa4Z^y+BF5;E%xl>Rj>^n7_92&uuzLkgwJVFrUeJg5Nxg?5i3CQE-IUAh93{5YUc*;xF@==d9Hh zKkb4+03ZMa(jzcfw;)L^c*HDyQl-aaStI*>rAvbhfq)?hC@;8dsl}Q_u5)NW%%&Gm zl)CrV`oAs2F>!kB)VZiIxDN!7 zlQit8Uy!mq1bD!VILrg!a&@I7HD%xD9YE!Yft-K<5Xct+PjOj@GncMh9Q|tLn-5Z} z9s=#^6{$KU@7HdAsTP_aza z4CK;*z+|VIWf+p0e@t!d;hUy?TBZq9BYA+mp~?<)s!75zQVUC(;D#bweX%@~i}*KR z{>v|8Ex;s)$A-YUIqr{@pXYO6jGW9~v2e?o!L%6bFH42fpUq8I-dFR9YLoi6yGMDq zjkPXh4Aw&`(YP7T>qd#QV|$dxNbRRA&3a<@BB`WG5$Sy)4v~MN+bN0YhX71dKw!9|3RCxlz+j_a+9-l-zdAUn^N80fV9$l(t|f`rCIt2OU;kM-vayuA0Pk(G$RmLO*Sb>q^0J7u-21s;WrS_ zivU|`cD1{;wG}x7G{aI0!QSt=2t3jjt0+JH_Ukl!3cmocz(OD(kOhJMdmMYxkM?AW zGYQVa=6oW$O@~oU77)LIKvfX9{MPeN_$_I7=9-e3O>qSVuVCRL95CIb5WzPPC>McQ z(^->}%(T=huv(?W39Ebf1_D5!90W$Zi#L!Ri`2Bvl-7s0;`Oo1DJOCP0<}Uw9$Y@~ zWi+qgu}IB{@G2G_fg8Ow<|U2iKmZ72MS%Inyo;Kj4og3Ab6O3pqkkO+C+-1({18xt zo;8&fmRn*{b0RzEa_7boD=j(j{f#6aPbTXBt>9E=;)PX^U_S!6b~knz7BzQcoy~PWB?JO^a9fKCJcxI`~;z1jfkh%H5Ho3nR8FPALRenen$eXIBlbsb{d}3JHAMia?OWT!yH+UUd0N zC$%b&wB(-G5G{WbiMr36LN5FS0ulkT!aQpBuM|IM>gq zFl9q%3aQ7+O{h5QbgBfCyw^MK?C=MpWD~?>pUv6`n7%vmKllLC}(I33{C*S_uXZil=CqKRR#!o(X>Hh(c C60NWR diff --git a/_site/assets/img/icons/icon-menu.svg b/_site/assets/img/icons/icon-menu.svg deleted file mode 100644 index 222352e88..000000000 --- a/_site/assets/img/icons/icon-menu.svg +++ /dev/null @@ -1,13 +0,0 @@ - - - - - - - - - - - - diff --git a/_site/assets/js/page_nav.js b/_site/assets/js/page_nav.js deleted file mode 100644 index 0f6d4e201..000000000 --- a/_site/assets/js/page_nav.js +++ /dev/null @@ -1,35 +0,0 @@ -// If the current page contains an element with id="page-nav" -// then this script will populate it with
  • elements -// containing links to all the

    elements on the current page -if (!!document.getElementById("page-nav")){ - - var headings = document.querySelectorAll("h2[id]"); - - for (var i = 0; i < headings.length; i++) { - document.getElementById("page-nav").innerHTML += - ''; - } - - $(document).ready(function() { - $(window).scroll(function() { - - var found = false; - var scrollPos = $(window).scrollTop(); - for (var i = 0; i < headings.length; i++) { - - if (scrollPos >= headings[i].offsetTop){ - found = true; - $("#nav-"+headings[i].id).addClass('current'); - } else { - $("#nav-"+headings[i].id).removeClass('current'); - } - - } - - }); - }); - -} \ No newline at end of file diff --git a/_site/compilers/index.html b/_site/compilers/index.html deleted file mode 100644 index 629c2ab8f..000000000 --- a/_site/compilers/index.html +++ /dev/null @@ -1,411 +0,0 @@ - - - - - - - - Fortran Compilers - Fortran Programming Language - - - - - - - - - - - - - - - - -
    -
    - - -
    -

    News

    - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    Fortran newsletter: June 2020   01 Jun 2020
    Fortran newsletter: May 2020   01 May 2020
    Open Source Directions Fortran webinar   18 Apr 2020
    Announcing FortranCon 2020   06 Apr 2020
    J3 February 2020 Meeting   28 Feb 2020
    -

    More…

    - -
    - - - - - - - -
    - -
    -
    - - - - - - - - - - - - - diff --git a/_site/favicon.ico b/_site/favicon.ico deleted file mode 100644 index a3603903a25b295d0a3e5019494454005dfbe159..0000000000000000000000000000000000000000 GIT binary patch literal 0 HcmV?d00001 literal 16958 zcmeI3?Nb{?7{IU75B=yjKU!aB`e$_fY?DaUQ7ctD&ghIEl)I$$4Tw&yj#C{Sn}k$_ zA~>}5r7a>YP$^@fU`wG$c?mC;m)2nru@o92g*@()<7n^P+ug))bJ=t=o6YXt?d|V* z_VzW8qHG|aty>lHeZR8hQAN2|QIsvjlO!cbJf>&jqQ1aG5uc`od|G4JrwxU@>dmlM z19$sW9b>6FdsH>Nz39Po*`wR`+!yv}QNp?6ZdM^(B*Q-cQPib~9Ks&;Il{as0k^fC z#v>kW2TKNoxkN&4lN=&GwU{OY@}3vU&VHNE|LmPI2ziPgCV4Wpd6VvM^K0?XxA`A1 zWI)mn-;rl`k5uU)uU3uxtGZ9x@&6b+2u`{7$~q@yoWwC9E4?3gYwKae(1L>QY~ z!+*$8{gbw)HW2m^7JqGN)T!nVZRNF2wtsw9j5nt}{&v_g{?;##JI%kq(mm!??s^Y; zYJY*ghISY}+YRHL{V+8+1~+GKWF(j5$_o5_Z5pPBCt&i@5d7ZW3xmxUptrsaj=uh} z)BKq~&*z86{Z)WGqHZcS4i$x^nLpEoYp-jUM@8}B)Q5+pV#oJm^jwcHe@?Y;!L}AV z(<#hf^Xf;^>3`to^TPb!yz)U_^H;sJS3dsJ;`*8;{}s;%x%@cKn46k0 z`HAir_deb{X1((J)8PMVM=_U!HlEH-OmXj9FFszm{f!;M`v2nTx40ZPrf2_Co-F(a zpL&DIUskZ2I-it4~`zoOO*cq6g zxlRXPP37_9zEaos&462vmRMk`ObAmse{SOvD${^GAPw!8yQt;zknC5u; z$1_Blb434X?EmrfUtU;3!{Dxe@LZARa*ZF~0a_ox)IV8MCKlo}{M3I}vfbZV%foR- z)baF>W#iep)v@@iU*2cEd@b&T{s+=H{}AEtt!stEeB9(wCRVu{@uvONYrNJUxyWyD ziH5B6S4a5MIR6yUzbH3ehvx}Par-?4C-_&cXk(o!^)Wr$of~*)}~`My@&m{sm&^Gs+rsq~<3!T@kN#I$!y98!>+%U-^lx zms<8%;1R;_3j2p__cNULKV|=bHXvvp$7%zT=G7oOy45z2kd%|Qc3iaDg%UfMo%zBa z@u<6W&6~eNK7TL|WKd$JHpj@A@C=bbTtYb{LO%5cGc7%Kpg`M9_`fFJc3j9I`K0Wh zv5%wE+NY-aMUOwQI!7Aj*$TNsCaL-SFxDAu`_R78o={PedS+=t4>w=e!+XZ`a8rvO jZVc+-1|!s?cfZ{t0YfiF*rHc# - - - - - - - Home - Fortran Programming Language - - - - - - - - - - - - - - - - -
    -

    High-performance parallel programming language

    -

    Get started

    -
    - -
    -
    -
    -

    Features

    - -

    High performance

    - Fortran has been designed from the ground-up for computationally - intensive applications in science and engineering. - Mature and battle-tested compilers and libraries allow you to write - code that runs close to the metal, fast. - -

    Statically and strongly typed

    - Fortran is statically and strongly typed, which allows the - compiler to catch many programming errors early on for you. - This also allows the compiler to generate efficient binary code. - -

    Easy to learn and use

    - Fortran is a relatively small language that is surprisingly easy - to learn and use. - Expressing most mathematical and arithmetic operations over large - arrays is as simple as you'd write them as equations on a whiteboard. - -

    Versatile

    - Fortran allows you to write code in a style that best fits your problem: - Imperative, procedural, array-oriented, object-oriented, or functional. - -

    Natively parallel

    - Fortran is a natively parallel programming language - with intuitive array-like syntax to communicate data between CPUs. - You can run almost the same code on a single CPU, - on a shared-memory multicore system, or on a distributed-memory - HPC or cloud-based system. - Coarrays, teams, events, and collective subroutines - allow you to express different parallel programming patterns - that best fit your problem at hand. - -
    - -
    - -
    -

    News

    - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    Fortran newsletter: June 2020   01 Jun 2020
    Fortran newsletter: May 2020   01 May 2020
    Open Source Directions Fortran webinar   18 Apr 2020
    Announcing FortranCon 2020   06 Apr 2020
    J3 February 2020 Meeting   28 Feb 2020
    - - -

    More…

    -
    - - - - -
    -
    -
    -
    - -
    -
    -
    -

    FAQ

    - -
    -

    What is the status of Fortran?

    - Fortran is still in active development. - The latest revision of the language is Fortran 2018, - and the next one, with the working title Fortran 202x, - is planned for release in the next few years. - Further, open source projects like the - Standard Library - and the - Fortran Package Manager - are in active development. - -

    What is Fortran used for?

    - Fortran is mostly used in domains that adopted computation - early--science and engineering. - These include numerical weather and ocean prediction, - computational fluid dynamics, applied math, statistics, and finance. - Fortran is the dominant language of High Performance Computing, - and is used to - benchmark the fastest supercomputers in the world. - -

    Should I use Fortran for my new project?

    - If you're writing a program or a library to perform fast arithmetic - computation over large numeric arrays, Fortran is the optimal tool - for the job. - -
    -
    - -
    -

    Join us!

    - -

    Mailing list

    - -

    Subscribe to our mailing list -to discuss anything Fortran related, announce Fortran projects, discuss development -of core fortran-lang.org projects (stdlib, fpm), and get -the latest news.

    - - -

    Discourse

    -

    - Join the discussion about all things Fortran on the - fortran-lang discourse. -

    - - -

    Twitter

    - - - - - - - -

    RSS feed

    -

    RSS clients can follow the RSS feed.

    - - -

    Open source

    -

    - Contribute code, report bugs and request features at - GitHub. -

    - -
    - -
    -
    - -
    -
    -

    Make Fortran better

    - -
    -

    Write proposals

    -

    - Have an idea about how to improve the language? - You can write new proposals or contribute to existing proposals - to the Fortran Standard Committee - on GitHub. -

    -
    - -
    -

    Develop tools

    -

    - You can also help make Fortran better by contributing to its - suite of tools, such as - Standard Library, - Package Manager, or - this website. -

    -
    - -
    -
    - - -
    -
    - -
    -

    Write Fortran software

    -

    - Or just write Fortran software for your research, business, or schoolwork. - You can learn how to get started here. -

    -
    - -
    -
    - - - - - - - - - - - - - diff --git a/_site/learn/best_practices.html b/_site/learn/best_practices.html deleted file mode 100644 index aef773879..000000000 --- a/_site/learn/best_practices.html +++ /dev/null @@ -1,244 +0,0 @@ - - - - - - - - Fortran best practices - Fortran Programming Language - - - - - - - - - - - - - - - - -
    -
    - - -
    -

    News

    - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    Fortran newsletter: June 2020   01 Jun 2020
    Fortran newsletter: May 2020   01 May 2020
    Open Source Directions Fortran webinar   18 Apr 2020
    Announcing FortranCon 2020   06 Apr 2020
    J3 February 2020 Meeting   28 Feb 2020
    -

    More…

    - -
    - - - - - - - -
    - -
    -
    - - - - - - - - - - - - - diff --git a/_site/learn/index.html b/_site/learn/index.html deleted file mode 100644 index cbac9e304..000000000 --- a/_site/learn/index.html +++ /dev/null @@ -1,331 +0,0 @@ - - - - - - - - Learn Fortran - Fortran Programming Language - - - - - - - - - - - - - - - - -
    -

    Learn Fortran

    -

    Learning resources for beginners and experts alike

    -
    - -
    -
    -

    Getting Started

    - -
    -

    - New to Fortran

    -

    - Try the quickstart Fortran tutorial, to - get an overview of the language syntax and capabilities. -

    - - - Quickstart tutorial - - -
    - -
    -

    - Looking for help

    -

    - Ask a question in the Fortran-lang discourse - a forum - for friendly discussion of all things Fortran. - -

    - - - Fortran-lang Discourse - - -
    - -
    -
    -
    - -
    -
    - -

    Mini-book Tutorials

    - - - -

    - - - - Getting started

    - -
    - - - -
    -

    - - - Quickstart Fortran Tutorial -

    -

    An introduction to the Fortran syntax and its capabilities

    -
    - -
    - - - -
    -
    -
    - -
    -
    - -

    Other Resources

    - -

    On the web

    - - -

    In print

    - - -
    -
    - - - - - - - - - - - - - - diff --git a/_site/learn/quickstart.html b/_site/learn/quickstart.html deleted file mode 100644 index 3fe1fda34..000000000 --- a/_site/learn/quickstart.html +++ /dev/null @@ -1,469 +0,0 @@ - - - - - - - - Quickstart tutorial - Fortran Programming Language - - - - - - - - - - - - - - - - -
    -
    - - - - - - - -
    -
    - - - - - - - - - - - - - diff --git a/_site/learn/quickstart/arrays_strings.html b/_site/learn/quickstart/arrays_strings.html deleted file mode 100644 index 99f319bda..000000000 --- a/_site/learn/quickstart/arrays_strings.html +++ /dev/null @@ -1,631 +0,0 @@ - - - - - - - - Arrays and strings - Fortran Programming Language - - - - - - - - - - - - - - - - -
    -
    - - - - - - - -
    -
    - - - - - - - - - - - - - diff --git a/_site/learn/quickstart/derived_types.html b/_site/learn/quickstart/derived_types.html deleted file mode 100644 index 3c488a7ab..000000000 --- a/_site/learn/quickstart/derived_types.html +++ /dev/null @@ -1,804 +0,0 @@ - - - - - - - - Derived types - Fortran Programming Language - - - - - - - - - - - - - - - - -
    -
    - - - - - - - -
    -
    - - - - - - - - - - - - - diff --git a/_site/learn/quickstart/hello_world.html b/_site/learn/quickstart/hello_world.html deleted file mode 100644 index d19d58080..000000000 --- a/_site/learn/quickstart/hello_world.html +++ /dev/null @@ -1,543 +0,0 @@ - - - - - - - - Hello World - Fortran Programming Language - - - - - - - - - - - - - - - - -
    -
    - - - - - - - -
    -
    - - - - - - - - - - - - - diff --git a/_site/learn/quickstart/operators_control_flow.html b/_site/learn/quickstart/operators_control_flow.html deleted file mode 100644 index 92eff5c4e..000000000 --- a/_site/learn/quickstart/operators_control_flow.html +++ /dev/null @@ -1,670 +0,0 @@ - - - - - - - - Operators and Control Flow - Fortran Programming Language - - - - - - - - - - - - - - - - -
    -
    - - - - - - - -
    -
    - - - - - - - - - - - - - diff --git a/_site/learn/quickstart/organising_code.html b/_site/learn/quickstart/organising_code.html deleted file mode 100644 index f8f7ea0b7..000000000 --- a/_site/learn/quickstart/organising_code.html +++ /dev/null @@ -1,671 +0,0 @@ - - - - - - - - Organising code structure - Fortran Programming Language - - - - - - - - - - - - - - - - -
    -
    - - - - - - - -
    -
    - - - - - - - - - - - - - diff --git a/_site/learn/quickstart/variables.html b/_site/learn/quickstart/variables.html deleted file mode 100644 index 75ed6a64b..000000000 --- a/_site/learn/quickstart/variables.html +++ /dev/null @@ -1,708 +0,0 @@ - - - - - - - - Variables - Fortran Programming Language - - - - - - - - - - - - - - - - -
    -
    - - - - - - - -
    -
    - - - - - - - - - - - - - diff --git a/_site/news/archive/index.html b/_site/news/archive/index.html deleted file mode 100644 index b05a1e16e..000000000 --- a/_site/news/archive/index.html +++ /dev/null @@ -1,188 +0,0 @@ - - - - - - - - News archive - Fortran Programming Language - - - - - - - - - - - - - - - - -
    -
    - - -
    -
    - - - - - - - - - - - - - diff --git a/_site/news/index.html b/_site/news/index.html deleted file mode 100644 index 192f2042d..000000000 --- a/_site/news/index.html +++ /dev/null @@ -1,741 +0,0 @@ - - - - - - - - News - Fortran Programming Language - - - - - - - - - - - - - - - - -
    -
    - - -
    -

    News

    - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    Fortran newsletter: June 2020   01 Jun 2020
    Fortran newsletter: May 2020   01 May 2020
    Open Source Directions Fortran webinar   18 Apr 2020
    Announcing FortranCon 2020   06 Apr 2020
    J3 February 2020 Meeting   28 Feb 2020
    -

    More…

    - -
    - - - - - - - -
    - -
    -
    - -
    -
    -
    - - See the - news archive for older posts -
    -
    - -
    - - - - - - - - - - - - - diff --git a/_site/newsletter/2020/02/28/J3-february-meeting/index.html b/_site/newsletter/2020/02/28/J3-february-meeting/index.html deleted file mode 100644 index 644c6c54d..000000000 --- a/_site/newsletter/2020/02/28/J3-february-meeting/index.html +++ /dev/null @@ -1,251 +0,0 @@ - - - - - - - - J3 February 2020 Meeting - Fortran Programming Language - - - - - - - - - - - - - - - - -
    -
    - -
    -
    - - - - - - - - - - - - - diff --git a/_site/newsletter/2020/04/06/Announcing-FortranCon-2020/index.html b/_site/newsletter/2020/04/06/Announcing-FortranCon-2020/index.html deleted file mode 100644 index 7bb0f43fb..000000000 --- a/_site/newsletter/2020/04/06/Announcing-FortranCon-2020/index.html +++ /dev/null @@ -1,182 +0,0 @@ - - - - - - - - Announcing FortranCon 2020 - Fortran Programming Language - - - - - - - - - - - - - - - - -
    -
    - -
    -
    - - - - - - - - - - - - - diff --git a/_site/newsletter/2020/04/18/Fortran-Webinar/index.html b/_site/newsletter/2020/04/18/Fortran-Webinar/index.html deleted file mode 100644 index 687461bcc..000000000 --- a/_site/newsletter/2020/04/18/Fortran-Webinar/index.html +++ /dev/null @@ -1,178 +0,0 @@ - - - - - - - - Open Source Directions Fortran webinar - Fortran Programming Language - - - - - - - - - - - - - - - - -
    -
    - -
    -
    - - - - - - - - - - - - - diff --git a/_site/newsletter/2020/05/01/Fortran-Newsletter-May-2020/index.html b/_site/newsletter/2020/05/01/Fortran-Newsletter-May-2020/index.html deleted file mode 100644 index f3680b7cf..000000000 --- a/_site/newsletter/2020/05/01/Fortran-Newsletter-May-2020/index.html +++ /dev/null @@ -1,295 +0,0 @@ - - - - - - - - Fortran newsletter: May 2020 - Fortran Programming Language - - - - - - - - - - - - - - - - -
    -
    - -
    -
    - - - - - - - - - - - - - diff --git a/_site/newsletter/2020/06/01/Fortran-Newsletter-June-2020/index.html b/_site/newsletter/2020/06/01/Fortran-Newsletter-June-2020/index.html deleted file mode 100644 index a41be1304..000000000 --- a/_site/newsletter/2020/06/01/Fortran-Newsletter-June-2020/index.html +++ /dev/null @@ -1,300 +0,0 @@ - - - - - - - - Fortran newsletter: June 2020 - Fortran Programming Language - - - - - - - - - - - - - - - - -
    -
    - -
    -
    - - - - - - - - - - - - - diff --git a/_site/packages/data-types.html b/_site/packages/data-types.html deleted file mode 100644 index 46c580f98..000000000 --- a/_site/packages/data-types.html +++ /dev/null @@ -1,436 +0,0 @@ - - - - - - - - Data types and containers - Fortran Programming Language - - - - - - - - - - - - - - - - -
    -

    Featured Open Source Projects

    -

    A rich ecosystem of high-performance code

    -
    - -
    -
    -
    - -

    Packages / - - - - Data types and containers

    -

    - Libraries for advanced data types and container classes -

    - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -

    - - coretran

    - - - -
    - Core fortran routines and object-oriented classes for sorting, kD-Trees, and other algorithms to handle scientific data and concepts -
    - Tags: dynamic array formatting debugging errors kdtree sorting random binary search strings unit testing timing -

    - - Fortran template library

    - - - - - -
    - Generic containers, versatile algorithms, easy string manipulation, and more -
    - Tags: resizeable array container linked list hash map regex string shared pointer -

    - - PENF

    - - - -
    - Provides portable kind-parameters and many useful procedures to deal with them -
    - Tags: kinds integer real ieee floating point floats precision -

    - - M_time

    - - - -
    - Procedures that expand on the Fortran DATE_AND_TIME intrinsic -
    - Tags: date weekday unix epoch month convert moon phases duration -

    - - fdict

    - - - -
    - Variable and type-free dictionary -
    - Tags: hash table -

    - - kdtree2

    - - - -
    - A kd-tree implementation in fortran -
    - Tags: -

    - - datetime-fortran

    - - - -
    - Date and time manipulation -
    - Tags: day year month calendar weekday clock -

    - - qContainers

    - - - -
    - Store any intrinsic or derived data type to a container -
    - Tags: qlibc tree table hash table linked list vector dynamic array unique set -

    - - Lookup Table Fortran

    - - - -
    - Linear lookup table implemented in modern Fortran -
    - Tags: -

    - - - - - FyCollections

    - - - -
    - generic collection templates for Fortran -
    - Tags: -
    - -
    - -
    -
    - -
    -
    -
    - - - See - - here for how to get your project listed. - -
    -
    - - - - - - - - - - - - - diff --git a/_site/packages/examples.html b/_site/packages/examples.html deleted file mode 100644 index 1bd65a042..000000000 --- a/_site/packages/examples.html +++ /dev/null @@ -1,283 +0,0 @@ - - - - - - - - Examples and templates - Fortran Programming Language - - - - - - - - - - - - - - - - -
    -

    Featured Open Source Projects

    -

    A rich ecosystem of high-performance code

    -
    - -
    -
    -
    - -

    Packages / - - - - Examples and templates

    -

    - Demonstration codes and templates for Fortran -

    - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -

    - - tcp-client-server

    - - - -
    - A minimal Fortran TCP client and server demonstrating c interoperability -
    - Tags: -

    - - Fortran 2018 examples

    - - - - - -
    - Easy examples of scientific computing with modern, powerful, easy Fortran 2018 standard -
    - Tags: block coarray contiguous mpi namelist openmp random submodule iso_fortran_env -

    - - Fortran patterns

    - - - -
    - Popular design patterns implemented in Fortran -
    - Tags: -

    - - Numerical methods in fortran

    - - - -
    - Solving linear, nonlinear equations, ordinary differential equations -
    - Tags: ode pde integral stochastic quadrature plotting -
    - -
    - -
    -
    - -
    -
    -
    - - - See - - here for how to get your project listed. - -
    -
    - - - - - - - - - - - - - diff --git a/_site/packages/graphics.html b/_site/packages/graphics.html deleted file mode 100644 index 73aae9d76..000000000 --- a/_site/packages/graphics.html +++ /dev/null @@ -1,385 +0,0 @@ - - - - - - - - Graphics, plotting and user interfaces - Fortran Programming Language - - - - - - - - - - - - - - - - -
    -

    Featured Open Source Projects

    -

    A rich ecosystem of high-performance code

    -
    - -
    -
    -
    - -

    Packages / - - - - Graphics, plotting and user interfaces

    -

    - Libraries for plotting data, handling images and generating user interfaces -

    - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -

    - - - f03gl

    - - - -
    - Fortran 2003 interface to OpenGL -
    - Tags: graphics interface opengl -

    - - - PLplot

    - - - - - -
    - Library for scientific plotting -
    - Tags: plot surface contour interface -

    - - pyplot-fortran

    - - - -
    - For generating plots from Fortran using Python's matplotlib.pyplot -
    - Tags: pyplot matplotlib contour histogram -

    - - ogpf

    - - - -
    - Object based interface to GnuPlot for Fortran -
    - Tags: animation plot surface contour -

    - - gtk-fortran

    - - - -
    - A cross-platform library to build Graphical User Interfaces (GUI) -
    - Tags: gui gtk graphical user interface -

    - - M_draw

    - - - -
    - Low-level vector graphics library -
    - Tags: -

    - - fortran-xlib

    - - - -
    - A collection of ISO C binding interfaces to Xlib for Fortran 2003 -
    - Tags: x11 mandelbrot raycast wireframe -

    - - fortran-sdl2

    - - - -
    - A collection of ISO C binding interfaces to Simple DirectMedia Layer 2.0 (SDL 2.0), for multimedia and game programming in Fortran -
    - Tags: -
    - -
    - -
    -
    - -
    -
    -
    - - - See - - here for how to get your project listed. - -
    -
    - - - - - - - - - - - - - diff --git a/_site/packages/index.html b/_site/packages/index.html deleted file mode 100644 index 99d439325..000000000 --- a/_site/packages/index.html +++ /dev/null @@ -1,566 +0,0 @@ - - - - - - - - Fortran Packages - Fortran Programming Language - - - - - - - - - - - - - - - - -
    -

    Fortran Packages

    -

    A rich ecosystem of high-performance code

    -
    - -
    -
    -

    Fortran-lang community projects

    - -
    -

    - Fortran Standard Library (stdlib)

    -

    - A community-driven project for a de facto "standard" library for Fortran. - The stdlib project is both a specification and a reference implementation, developed in - cooperation with the Fortran Standards Committee. - Find out more on - - GitHub. -

    - - - - - - - - - - - - - -
    - -
    - - -
    -

    - Fortran Package Manager (fpm)

    -

    - A prototype project to develop a common build system for Fortran packages - and their dependencies. - Find out more on - - GitHub. -

    - - - - - - - - - - - - -
    - - -
    - -
    -

    - fortran-lang.org

    -

    - This website is open source and contributions are welcome! - Find out more on - - GitHub. -

    - - - - - - - - - - - - -
    - -
    - - -
    -
    - -
    -
    -

    Featured open source projects

    - -
    - - -
    - -

    Browse by category

    -
    - - - - - - - - - - - - - - - - - - - - - -
    -

    - - - - - Data types and containers - - (10) -

    -

    Libraries for advanced data types and container classes

    -
    - - - - - - - - - - - -
    -

    - - - - - Examples and templates - - (4) -

    -

    Demonstration codes and templates for Fortran

    -
    - - - - - - - -
    -

    - - - - - Graphics, plotting and user interfaces - - (8) -

    -

    Libraries for plotting data, handling images and generating user interfaces

    -
    - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    -

    - - - - - Interface libraries - - (17) -

    -

    Libraries that interface with other systems, languages, or devices

    -
    - - - - - - - -
    -

    - - - - - Input, output and parsing - - (16) -

    -

    Libraries for reading, writing and parsing files and inputs

    -
    - - - - - - - -
    -

    - - - - - Libraries - - (9) -

    -

    Fortran libraries for general programming tasks

    -
    - - - - - - - - - - - -
    -

    - - - - - Numerical projects - - (21) -

    -

    Fortran libraries for linear algebra, optimization, root-finding etc.

    -
    - - - - - - - - - - - - - - - - - - - - - -
    -

    - - - - - Programming utilities - - (7) -

    -

    Error handling, logging, documentation and testing

    -
    - - - - - - - - - - - - - - - -
    -

    - - - - - Scientific Codes - - (16) -

    -

    Applications and libraries for applied mathematical and scientific problems

    -
    - - - - - - - - - - - -
    -

    - - - - - Characters and strings - - (5) -

    -

    Libraries for manipulating characters and strings

    -
    - - - - - - - - -
    -
    -
    - -
    -
    -
    - - See - - here for how to get your project listed. - -
    -
    - - - - - - - - - - - - - - diff --git a/_site/packages/interfaces.html b/_site/packages/interfaces.html deleted file mode 100644 index c5b7605fd..000000000 --- a/_site/packages/interfaces.html +++ /dev/null @@ -1,620 +0,0 @@ - - - - - - - - Interface libraries - Fortran Programming Language - - - - - - - - - - - - - - - - -
    -

    Featured Open Source Projects

    -

    A rich ecosystem of high-performance code

    -
    - -
    -
    -
    - -

    Packages / - - - - Interface libraries

    -

    - Libraries that interface with other systems, languages, or devices -

    - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -

    - - forpy

    - - - - - -
    - allows you to use Python features in Fortran -
    - Tags: dict list tuple numpy python matplotlib scipy -

    - - tcp-client-server

    - - - -
    - A minimal Fortran TCP client and server demonstrating c interoperability -
    - Tags: -

    - - clfortran

    - - - - - -
    - Fortran interfaces to Khronos OpenCL 1.2 API -
    - Tags: gpu compute accelerator -

    - - M_process

    - - - -
    - Read and write lines to or from a process from Fortran via a C wrapper -
    - Tags: -

    - - M_system

    - - - -
    - Call C system routines from Fortran -
    - Tags: posix putenv getenv setenv environment file system mkdir rename rmdir chmod rand uname -

    - - Focal

    - - - -
    - A module library which wraps calls to the OpenCL runtime API with a higher abstraction level -
    - Tags: gpu compute accelerator -

    - - - - - foryxima

    - - - -
    - File system manipulation and unit testing framework -
    - Tags: posix libc -

    - - - - - sqliteff

    - - - -
    - A thin wrapper around the SQLite library -
    - Tags: sql database -

    - - - f03gl

    - - - -
    - Fortran 2003 interface to OpenGL -
    - Tags: graphics interface opengl -

    - - - PLplot

    - - - - - -
    - Library for scientific plotting -
    - Tags: plot surface contour interface -

    - - pyplot-fortran

    - - - -
    - For generating plots from Fortran using Python's matplotlib.pyplot -
    - Tags: pyplot matplotlib contour histogram -

    - - ogpf

    - - - -
    - Object based interface to GnuPlot for Fortran -
    - Tags: animation plot surface contour -

    - - gtk-fortran

    - - - -
    - A cross-platform library to build Graphical User Interfaces (GUI) -
    - Tags: gui gtk graphical user interface -

    - - fortran-xlib

    - - - -
    - A collection of ISO C binding interfaces to Xlib for Fortran 2003 -
    - Tags: x11 mandelbrot raycast wireframe -

    - - fortran-sdl2

    - - - -
    - A collection of ISO C binding interfaces to Simple DirectMedia Layer 2.0 (SDL 2.0), for multimedia and game programming in Fortran -
    - Tags: -

    - - fortranlib

    - - - -
    - Collection of personal scientific routines in Fortran -
    - Tags: solver integral integrate interpolation histogram constants hdf5 error random posix angles probability stokes vectors -

    - - fgsl

    - - - -
    - Fortran interface to the GNU Scientific Library -
    - Tags: -
    - -
    - -
    -
    - -
    -
    -
    - - - See - - here for how to get your project listed. - -
    -
    - - - - - - - - - - - - - diff --git a/_site/packages/io.html b/_site/packages/io.html deleted file mode 100644 index 94fbdd96a..000000000 --- a/_site/packages/io.html +++ /dev/null @@ -1,589 +0,0 @@ - - - - - - - - Input, output and parsing - Fortran Programming Language - - - - - - - - - - - - - - - - -
    -

    Featured Open Source Projects

    -

    A rich ecosystem of high-performance code

    -
    - -
    -
    -
    - -

    Packages / - - - - Input, output and parsing

    -

    - Libraries for reading, writing and parsing files and inputs -

    - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -

    - - fortran-utils

    - - - -
    - Various utilities for Fortran programs -
    - Tags: constants types sorting mesh spline ppm hdf5 lapack -

    - - json-fortran

    - - - -
    - A Fortran 2008 JSON API -
    - Tags: json io -

    - - VTKFortran

    - - - -
    - Library to parse and emit files conforming VTK (XML) standard -
    - Tags: -

    - - netCFD-Fortran

    - - - -
    - Fortran interfaces for netCFD C library. -
    - Tags: netcdf -

    - - fox

    - - - -
    - A Fortran XML library -
    - Tags: -

    - - FEconv

    - - - -
    - utility and library for converting between mesh and finite element field formats -
    - Tags: ansys msh nastran bdf vtk -

    - - h5fortran

    - - - -
    - Simple, robust, thin HDF5 polymorphic read/write interface -
    - Tags: hdf5 -

    - - nc4fortran

    - - - -
    - Object-oriented interface for NetCDF4 in Fortran -
    - Tags: netcdf -

    - - fortran-csv-module

    - - - -
    - Read and write CSV Files using modern Fortran -
    - Tags: -

    - - M_IO

    - - - - - -
    - Fortran module for common I/O tasks -
    - Tags: delete slurp swallow dirname split path -

    - - - - - jsonff

    - - - -
    - Routines for building JSON structures in Fortran -
    - Tags: -

    - - NPY for Fortran

    - - - -
    - Allows saving numerical Fortran arrays in Numpy's .npy or .npz format -
    - Tags: python -

    - - FiNeR

    - - - -
    - INI ParseR and generator -
    - Tags: config -

    - - config_fortran

    - - - -
    - Configuration file parser for Fortran -
    - Tags: -

    - - - - - Parser for Fortran

    - - - -
    - The foundations of a functional style parser combinator library -
    - Tags: -

    - - fortranlib

    - - - -
    - Collection of personal scientific routines in Fortran -
    - Tags: solver integral integrate interpolation histogram constants hdf5 error random posix angles probability stokes vectors -
    - -
    - -
    -
    - -
    -
    -
    - - - See - - here for how to get your project listed. - -
    -
    - - - - - - - - - - - - - diff --git a/_site/packages/libraries.html b/_site/packages/libraries.html deleted file mode 100644 index 1d88672df..000000000 --- a/_site/packages/libraries.html +++ /dev/null @@ -1,406 +0,0 @@ - - - - - - - - Libraries - Fortran Programming Language - - - - - - - - - - - - - - - - -
    -

    Featured Open Source Projects

    -

    A rich ecosystem of high-performance code

    -
    - -
    -
    -
    - -

    Packages / - - - - Libraries

    -

    - Fortran libraries for general programming tasks -

    - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -

    - - functional-fortran

    - - - -
    - Functional programming for modern Fortran -
    - Tags: functional filter fold map -

    - - fortran-utils

    - - - -
    - Various utilities for Fortran programs -
    - Tags: constants types sorting mesh spline ppm hdf5 lapack -

    - - Open Coarrays

    - - - -
    - A parallel application binary interface for Fortran 2018 compilers. -
    - Tags: mpi openshmem gfortran -

    - - FLAP

    - - - -
    - Fortran command Line Arguments Parser -
    - Tags: command line cli argument parser -

    - - Fortran Standard Library (stdlib)

    - - - -
    - A community driven and agreed upon de facto standard library for Fortran -
    - Tags: -

    - - coretran

    - - - -
    - Core fortran routines and object-oriented classes for sorting, kD-Trees, and other algorithms to handle scientific data and concepts -
    - Tags: dynamic array formatting debugging errors kdtree sorting random binary search strings unit testing timing -

    - - M_CLI

    - - - -
    - Unix-like command line argument parsing -
    - Tags: namelist args -

    - - M_history

    - - - -
    - Subroutine to give a line-mode command history to interactive programs -
    - Tags: redo -

    - - fortranlib

    - - - -
    - Collection of personal scientific routines in Fortran -
    - Tags: solver integral integrate interpolation histogram constants hdf5 error random posix angles probability stokes vectors -
    - -
    - -
    -
    - -
    -
    -
    - - - See - - here for how to get your project listed. - -
    -
    - - - - - - - - - - - - - diff --git a/_site/packages/numerical.html b/_site/packages/numerical.html deleted file mode 100644 index c7648449d..000000000 --- a/_site/packages/numerical.html +++ /dev/null @@ -1,721 +0,0 @@ - - - - - - - - Numerical projects - Fortran Programming Language - - - - - - - - - - - - - - - - -
    -

    Featured Open Source Projects

    -

    A rich ecosystem of high-performance code

    -
    - -
    -
    -
    - -

    Packages / - - - - Numerical projects

    -

    - Fortran libraries for linear algebra, optimization, root-finding etc. -

    - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -

    - - PENF

    - - - -
    - Provides portable kind-parameters and many useful procedures to deal with them -
    - Tags: kinds integer real ieee floating point floats precision -

    - - OpenBLAS

    - - - -
    - Optimized BLAS library based on GotoBLAS2 -
    - Tags: blas linear algebra -

    - - LAPACK

    - - - - - -
    - Routines for numerical linear algebra -
    - Tags: blas linear algera -

    - - ElmerFEM

    - - - -
    - Finite element software for numerical solution of partial differential equations -
    - Tags: pde fe -

    - - fortranlib

    - - - -
    - Collection of personal scientific routines in Fortran -
    - Tags: solver integral integrate interpolation histogram constants hdf5 error random posix angles probability stokes vectors -

    - - SHTOOLS

    - - - -
    - A Fortran-95/Python library that can be used to perform spherical harmonic transforms -
    - Tags: spectral analysis Slepian bases gravitational magnetic field openmp -

    - - ARPACK

    - - - - - -
    - Collection of Fortran77 subroutines designed to solve large scale eigenvalue problems. -
    - Tags: eigenvalue eigenvector singular value decomposition svd -

    - - neural-fortran

    - - - -
    - A parallel neural net microframework. -
    - Tags: back propagation coarray -

    - - ParaMonte

    - - - - - -
    - A general-purpose high-performance MPI/Coarray-parallel Monte Carlo simulation library implemented in Fortran 2018 with interfaces to C/C++/Fortran/MATLAB/Python -
    - Tags: parallel mpi coarray monte carlo mcmc c cpp matlab python statistics bayesian stochastic optimization sampling integration machine learning -

    - - bspline-fortran

    - - - -
    - Multidimensional B-Spline interpolation of data on a regular grid -
    - Tags: spline interpolation extrapolation integration integral -

    - - FOODIE

    - - - -
    - Fortran Object-Oriented Differential-equations Integration Environment -
    - Tags: ode pde euler runge kutta -

    - - fgsl

    - - - -
    - Fortran interface to the GNU Scientific Library -
    - Tags: -

    - - SciFortran

    - - - -
    - collection of fortran modules and procedures for scientific calculations. -
    - Tags: -

    - - Los Alamos Grid Toolbox (LaGriT)

    - - - - - -
    - a library of user callable tools that provide mesh generation, mesh optimization and dynamic mesh maintenance -
    - Tags: -

    - - DBCSR

    - - - -
    - Distributed block compresseed sparse row matrix library -
    - Tags: linear algebra parallel mpi openmp cuda hip -

    - - GALAHAD

    - - - - - -
    - Modules for nonlinear optimization -
    - Tags: least squares active set quadratic programming interior point convex programming linear programming -

    - - slsqp

    - - - -
    - SLSQP nonlinear constrained optimizer -
    - Tags: nonlinear programming equality inequality constraints -

    - - NumDiff

    - - - -
    - a modern Fortran interface for computing the Jacobian (derivative) matrix of m nonlinear functions which depend on n variables -
    - Tags: finite difference -

    - - - - - quaff

    - - - -
    - Quantities for Fortran. Make math with units more convenient -
    - Tags: -

    - - rng_fortran

    - - - - - -
    - Pseudo random number generator in Fortran, internally using xoroshiro128+ -
    - Tags: uniform normal poisson distributed -

    - - Numerical methods in fortran

    - - - -
    - Solving linear, nonlinear equations, ordinary differential equations -
    - Tags: ode pde integral stochastic quadrature plotting -
    - -
    - -
    -
    - -
    -
    -
    - - - See - - here for how to get your project listed. - -
    -
    - - - - - - - - - - - - - diff --git a/_site/packages/preview.html b/_site/packages/preview.html deleted file mode 100644 index f8496a7ec..000000000 --- a/_site/packages/preview.html +++ /dev/null @@ -1,204 +0,0 @@ - - - - - - - - Preview - Fortran Programming Language - - - - - - - - - - - - - - - - -
    -

    Featured Open Source Projects

    -

    A rich ecosystem of high-performance code

    -
    - -
    -
    -
    - -

    Packages / - - Preview

    -

    - Preview project badges -

    - - - - - - - - - - - - - - - - - - - - - -

    - - FORD

    - - - -
    - Automatic documentation generator for modern Fortran programs -
    - Tags: documentation -
    - -
    - -
    -
    - -
    -
    -
    - - - See - - here for how to get your project listed. - -
    -
    - - - - - - - - - - - - - diff --git a/_site/packages/programming.html b/_site/packages/programming.html deleted file mode 100644 index b4483eda9..000000000 --- a/_site/packages/programming.html +++ /dev/null @@ -1,370 +0,0 @@ - - - - - - - - Programming utilities - Fortran Programming Language - - - - - - - - - - - - - - - - -
    -

    Featured Open Source Projects

    -

    A rich ecosystem of high-performance code

    -
    - -
    -
    -
    - -

    Packages / - - - - Programming utilities

    -

    - Error handling, logging, documentation and testing -

    - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -

    - - coretran

    - - - -
    - Core fortran routines and object-oriented classes for sorting, kD-Trees, and other algorithms to handle scientific data and concepts -
    - Tags: dynamic array formatting debugging errors kdtree sorting random binary search strings unit testing timing -

    - - - - - foryxima

    - - - -
    - File system manipulation and unit testing framework -
    - Tags: posix libc -

    - - FORD

    - - - -
    - Automatic documentation generator for modern Fortran programs -
    - Tags: documentation -

    - - - - - vegetables

    - - - - - -
    - A Fortran testing framework written using functional programming principles. -
    - Tags: testing assert -

    - - pFUnit

    - - - -
    - Parallel Fortran Unit Testing Framework -
    - Tags: unit testing -

    - - - - - erloff

    - - - -
    - Errors and logging for fortran -
    - Tags: errors logging -

    - - - - - fytest

    - - - -
    - a lightweight unit testing framework for Fortran -
    - Tags: unit testing -
    - -
    - -
    -
    - -
    -
    -
    - - - See - - here for how to get your project listed. - -
    -
    - - - - - - - - - - - - - diff --git a/_site/packages/projects_json.js b/_site/packages/projects_json.js deleted file mode 100644 index e7a575702..000000000 --- a/_site/packages/projects_json.js +++ /dev/null @@ -1,953 +0,0 @@ -projects = [ - - { - "name": "functional-fortran", - "description": "Functional programming for modern Fortran", - "github": "wavebitscientific/functional-fortran", - "url": "", - "categories": "libraries", - "tags": "functional filter fold map", - "license": "" - }, - - { - "name": "fortran-utils", - "description": "Various utilities for Fortran programs", - "github": "certik/fortran-utils", - "url": "", - "categories": "libraries io", - "tags": "constants types sorting mesh spline ppm hdf5 lapack", - "license": "" - }, - - { - "name": "Open Coarrays", - "description": "A parallel application binary interface for Fortran 2018 compilers.", - "github": "sourceryinstitute/OpenCoarrays", - "url": "", - "categories": "libraries", - "tags": "mpi openshmem gfortran", - "license": "" - }, - - { - "name": "FLAP", - "description": "Fortran command Line Arguments Parser", - "github": "szaghi/FLAP", - "url": "", - "categories": "libraries", - "tags": "command line cli argument parser", - "license": "none" - }, - - { - "name": "Fortran Standard Library (stdlib)", - "description": "A community driven and agreed upon de facto standard library for Fortran", - "github": "fortran-lang/stdlib", - "url": "", - "categories": "libraries", - "tags": "", - "license": "" - }, - - { - "name": "coretran", - "description": "Core fortran routines and object-oriented classes for sorting, kD-Trees, and other algorithms to handle scientific data and concepts", - "github": "leonfoks/coretran", - "url": "", - "categories": "libraries strings data-types programming", - "tags": "dynamic array formatting debugging errors kdtree sorting random binary search strings unit testing timing", - "license": "" - }, - - { - "name": "M_CLI", - "description": "Unix-like command line argument parsing", - "github": "urbanjost/M_CLI", - "url": "", - "categories": "libraries", - "tags": "namelist args", - "license": "" - }, - - { - "name": "M_history", - "description": "Subroutine to give a line-mode command history to interactive programs", - "github": "urbanjost/M_history", - "url": "", - "categories": "libraries", - "tags": "redo", - "license": "" - }, - - { - "name": "forpy", - "description": "allows you to use Python features in Fortran", - "github": "ylikx/forpy", - "url": "", - "categories": "interfaces", - "tags": "dict list tuple numpy python matplotlib scipy", - "license": "GNU GPL v3" - }, - - { - "name": "tcp-client-server", - "description": "A minimal Fortran TCP client and server demonstrating c interoperability", - "github": "modern-fortran/tcp-client-server", - "url": "", - "categories": "interfaces examples", - "tags": "", - "license": "" - }, - - { - "name": "clfortran", - "description": "Fortran interfaces to Khronos OpenCL 1.2 API", - "github": "cass-support/clfortran", - "url": "", - "categories": "interfaces", - "tags": "gpu compute accelerator", - "license": "GNU GPL v3" - }, - - { - "name": "M_process", - "description": "Read and write lines to or from a process from Fortran via a C wrapper", - "github": "urbanjost/M_process", - "url": "", - "categories": "interfaces", - "tags": "", - "license": "" - }, - - { - "name": "M_system", - "description": "Call C system routines from Fortran", - "github": "urbanjost/M_system", - "url": "", - "categories": "interfaces", - "tags": "posix putenv getenv setenv environment file system mkdir rename rmdir chmod rand uname", - "license": "" - }, - - { - "name": "Focal", - "description": "A module library which wraps calls to the OpenCL runtime API with a higher abstraction level", - "github": "LKedward/focal", - "url": "", - "categories": "interfaces", - "tags": "gpu compute accelerator", - "license": "" - }, - - { - "name": "foryxima", - "description": "File system manipulation and unit testing framework", - "github": "", - "url": "https://bitbucket.org/aradi/fortyxima/src/develop/", - "categories": "interfaces programming", - "tags": "posix libc", - "license": "BSD 2-clause" - }, - - { - "name": "sqliteff", - "description": "A thin wrapper around the SQLite library", - "github": "", - "url": "https://gitlab.com/everythingfunctional/sqliteff", - "categories": "interfaces", - "tags": "sql database", - "license": "MIT" - }, - - { - "name": "FORD", - "description": "Automatic documentation generator for modern Fortran programs", - "github": "Fortran-FOSS-Programmers/ford", - "url": "", - "categories": "programming preview", - "tags": "documentation", - "license": "" - }, - - { - "name": "vegetables", - "description": "A Fortran testing framework written using functional programming principles.", - "github": "", - "url": "https://gitlab.com/everythingfunctional/vegetables", - "categories": "programming", - "tags": "testing assert", - "license": "MIT" - }, - - { - "name": "pFUnit", - "description": "Parallel Fortran Unit Testing Framework", - "github": "Goddard-Fortran-Ecosystem/pFUnit", - "url": "", - "categories": "programming", - "tags": "unit testing", - "license": "none" - }, - - { - "name": "erloff", - "description": "Errors and logging for fortran", - "github": "", - "url": "https://gitlab.com/everythingfunctional/erloff", - "categories": "programming", - "tags": "errors logging", - "license": "BSD 3-Clause" - }, - - { - "name": "fytest", - "description": "a lightweight unit testing framework for Fortran", - "github": "", - "url": "https://bitbucket.org/aradi/fytest/src/develop/", - "categories": "programming", - "tags": "unit testing", - "license": "BSD 2-clause" - }, - - { - "name": "Fortran template library", - "description": "Generic containers, versatile algorithms, easy string manipulation, and more", - "github": "SCM-NV/ftl", - "url": "", - "categories": "data-types", - "tags": "resizeable array container linked list hash map regex string shared pointer", - "license": "GNU GPL v3" - }, - - { - "name": "PENF", - "description": "Provides portable kind-parameters and many useful procedures to deal with them", - "github": "szaghi/PENF", - "url": "", - "categories": "data-types numerical", - "tags": "kinds integer real ieee floating point floats precision", - "license": "none" - }, - - { - "name": "M_time", - "description": "Procedures that expand on the Fortran DATE_AND_TIME intrinsic", - "github": "urbanjost/M_time", - "url": "", - "categories": "data-types", - "tags": "date weekday unix epoch month convert moon phases duration", - "license": "" - }, - - { - "name": "fdict", - "description": "Variable and type-free dictionary", - "github": "zerothi/fdict", - "url": "", - "categories": "data-types", - "tags": "hash table", - "license": "" - }, - - { - "name": "kdtree2", - "description": "A kd-tree implementation in fortran", - "github": "jmhodges/kdtree2", - "url": "", - "categories": "data-types", - "tags": "", - "license": "none" - }, - - { - "name": "datetime-fortran", - "description": "Date and time manipulation", - "github": "wavebitscientific/datetime-fortran", - "url": "", - "categories": "data-types", - "tags": "day year month calendar weekday clock", - "license": "none" - }, - - { - "name": "qContainers", - "description": "Store any intrinsic or derived data type to a container", - "github": "darmar-lt/qcontainers", - "url": "", - "categories": "data-types", - "tags": "qlibc tree table hash table linked list vector dynamic array unique set", - "license": "none" - }, - - { - "name": "Lookup Table Fortran", - "description": "Linear lookup table implemented in modern Fortran", - "github": "jannisteunissen/lookup_table_fortran", - "url": "", - "categories": "data-types", - "tags": "", - "license": "" - }, - - { - "name": "FyCollections", - "description": "generic collection templates for Fortran", - "github": "", - "url": "https://bitbucket.org/aradi/fycollections/src/develop/", - "categories": "data-types", - "tags": "", - "license": "BSD 2-Clause" - }, - - { - "name": "StringiFor", - "description": "Fortran strings manipulator", - "github": "szaghi/StringiFor", - "url": "", - "categories": "strings", - "tags": "split join basename search concat", - "license": "none" - }, - - { - "name": "M_strings", - "description": "Fortran string manipulations", - "github": "urbanjost/M_strings", - "url": "", - "categories": "strings", - "tags": "upper lower quoted join replace white space string conversion tokens split", - "license": "" - }, - - { - "name": "Strings for Fortran", - "description": "A library of string functions for Fortran.", - "github": "", - "url": "https://gitlab.com/everythingfunctional/strff", - "categories": "strings", - "tags": "", - "license": "MIT" - }, - - { - "name": "iso_varying_string", - "description": "Implementation of the Fortran ISO_VARYING_STRING module in accordance with the standard", - "github": "", - "url": "https://gitlab.com/everythingfunctional/iso_varying_string", - "categories": "strings", - "tags": "varying length character strings", - "license": "MIT" - }, - - { - "name": "json-fortran", - "description": "A Fortran 2008 JSON API", - "github": "jacobwilliams/json-fortran", - "url": "", - "categories": "io", - "tags": "json io", - "license": "none" - }, - - { - "name": "VTKFortran", - "description": "Library to parse and emit files conforming VTK (XML) standard", - "github": "szaghi/VTKFortran", - "url": "", - "categories": "io", - "tags": "", - "license": "none" - }, - - { - "name": "netCFD-Fortran", - "description": "Fortran interfaces for netCFD C library.", - "github": "Unidata/netcdf-fortran", - "url": "", - "categories": "io", - "tags": "netcdf", - "license": "none" - }, - - { - "name": "fox", - "description": "A Fortran XML library", - "github": "andreww/fox", - "url": "", - "categories": "io", - "tags": "", - "license": "none" - }, - - { - "name": "FEconv", - "description": "utility and library for converting between mesh and finite element field formats", - "github": "victorsndvg/FEconv", - "url": "", - "categories": "io", - "tags": "ansys msh nastran bdf vtk", - "license": "" - }, - - { - "name": "h5fortran", - "description": "Simple, robust, thin HDF5 polymorphic read/write interface", - "github": "scivision/h5fortran", - "url": "", - "categories": "io", - "tags": "hdf5", - "license": "" - }, - - { - "name": "nc4fortran", - "description": "Object-oriented interface for NetCDF4 in Fortran", - "github": "scivision/nc4fortran", - "url": "", - "categories": "io", - "tags": "netcdf", - "license": "" - }, - - { - "name": "fortran-csv-module", - "description": "Read and write CSV Files using modern Fortran", - "github": "jacobwilliams/fortran-csv-module", - "url": "", - "categories": "io", - "tags": "", - "license": "none" - }, - - { - "name": "M_IO", - "description": "Fortran module for common I/O tasks", - "github": "urbanjost/M_io", - "url": "", - "categories": "io", - "tags": "delete slurp swallow dirname split path", - "license": "Public domain" - }, - - { - "name": "jsonff", - "description": "Routines for building JSON structures in Fortran", - "github": "", - "url": "https://gitlab.com/everythingfunctional/jsonff", - "categories": "io", - "tags": "", - "license": "MIT" - }, - - { - "name": "NPY for Fortran", - "description": "Allows saving numerical Fortran arrays in Numpy's .npy or .npz format", - "github": "MRedies/NPY-for-Fortran", - "url": "", - "categories": "io", - "tags": "python", - "license": "" - }, - - { - "name": "FiNeR", - "description": "INI ParseR and generator", - "github": "szaghi/FiNeR", - "url": "", - "categories": "io", - "tags": "config", - "license": "none" - }, - - { - "name": "config_fortran", - "description": "Configuration file parser for Fortran", - "github": "jannisteunissen/config_fortran", - "url": "", - "categories": "io", - "tags": "", - "license": "" - }, - - { - "name": "Parser for Fortran", - "description": "The foundations of a functional style parser combinator library", - "github": "", - "url": "https://gitlab.com/everythingfunctional/parff", - "categories": "io", - "tags": "", - "license": "MIT" - }, - - { - "name": "f03gl", - "description": "Fortran 2003 interface to OpenGL", - "github": "", - "url": "http://www-stone.ch.cam.ac.uk/pub/f03gl/index.xhtml", - "categories": "graphics interfaces", - "tags": "graphics interface opengl", - "license": "GNU GPL v3" - }, - - { - "name": "PLplot", - "description": "Library for scientific plotting", - "github": "", - "url": "http://plplot.sourceforge.net/", - "categories": "graphics interfaces", - "tags": "plot surface contour interface", - "license": "GNU LGPL v3" - }, - - { - "name": "pyplot-fortran", - "description": "For generating plots from Fortran using Python's matplotlib.pyplot", - "github": "jacobwilliams/pyplot-fortran", - "url": "", - "categories": "graphics interfaces", - "tags": "pyplot matplotlib contour histogram", - "license": "none" - }, - - { - "name": "ogpf", - "description": "Object based interface to GnuPlot for Fortran", - "github": "kookma/ogpf", - "url": "", - "categories": "graphics interfaces", - "tags": "animation plot surface contour", - "license": "none" - }, - - { - "name": "gtk-fortran", - "description": "A cross-platform library to build Graphical User Interfaces (GUI)", - "github": "vmagnin/gtk-fortran", - "url": "", - "categories": "graphics interfaces", - "tags": "gui gtk graphical user interface", - "license": "" - }, - - { - "name": "M_draw", - "description": "Low-level vector graphics library", - "github": "urbanjost/M_draw", - "url": "", - "categories": "graphics", - "tags": "", - "license": "" - }, - - { - "name": "fortran-xlib", - "description": "A collection of ISO C binding interfaces to Xlib for Fortran 2003", - "github": "interkosmos/fortran-xlib", - "url": "", - "categories": "graphics interfaces", - "tags": "x11 mandelbrot raycast wireframe", - "license": "" - }, - - { - "name": "fortran-sdl2", - "description": "A collection of ISO C binding interfaces to Simple DirectMedia Layer 2.0 (SDL 2.0), for multimedia and game programming in Fortran", - "github": "interkosmos/fortran-sdl2", - "url": "", - "categories": "graphics interfaces", - "tags": "", - "license": "" - }, - - { - "name": "OpenBLAS", - "description": "Optimized BLAS library based on GotoBLAS2", - "github": "xianyi/OpenBLAS", - "url": "", - "categories": "numerical", - "tags": "blas linear algebra", - "license": "" - }, - - { - "name": "LAPACK", - "description": "Routines for numerical linear algebra", - "github": "Reference-LAPACK/lapack", - "url": "", - "categories": "numerical", - "tags": "blas linear algera", - "license": "BSD 3-Clause" - }, - - { - "name": "ElmerFEM", - "description": "Finite element software for numerical solution of partial differential equations", - "github": "ElmerCSC/elmerfem", - "url": "", - "categories": "numerical", - "tags": "pde fe", - "license": "" - }, - - { - "name": "fortranlib", - "description": "Collection of personal scientific routines in Fortran", - "github": "astrofrog/fortranlib", - "url": "", - "categories": "libraries numerical io interfaces", - "tags": "solver integral integrate interpolation histogram constants hdf5 error random posix angles probability stokes vectors", - "license": "" - }, - - { - "name": "SHTOOLS", - "description": "A Fortran-95/Python library that can be used to perform spherical harmonic transforms", - "github": "SHTOOLS/SHTOOLS", - "url": "", - "categories": "numerical", - "tags": "spectral analysis Slepian bases gravitational magnetic field openmp", - "license": "" - }, - - { - "name": "ARPACK", - "description": "Collection of Fortran77 subroutines designed to solve large scale eigenvalue problems.", - "github": "opencollab/arpack-ng", - "url": "", - "categories": "numerical", - "tags": "eigenvalue eigenvector singular value decomposition svd", - "license": "BSD 3-Clause" - }, - - { - "name": "neural-fortran", - "description": "A parallel neural net microframework.", - "github": "modern-fortran/neural-fortran", - "url": "", - "categories": "numerical", - "tags": "back propagation coarray", - "license": "" - }, - - { - "name": "ParaMonte", - "description": "A general-purpose high-performance MPI/Coarray-parallel Monte Carlo simulation library implemented in Fortran 2018 with interfaces to C/C++/Fortran/MATLAB/Python", - "github": "cdslaborg/paramonte", - "url": "", - "categories": "numerical", - "tags": "parallel mpi coarray monte carlo mcmc c cpp matlab python statistics bayesian stochastic optimization sampling integration machine learning", - "license": "" - }, - - { - "name": "bspline-fortran", - "description": "Multidimensional B-Spline interpolation of data on a regular grid", - "github": "jacobwilliams/bspline-fortran", - "url": "", - "categories": "numerical", - "tags": "spline interpolation extrapolation integration integral", - "license": "none" - }, - - { - "name": "FOODIE", - "description": "Fortran Object-Oriented Differential-equations Integration Environment", - "github": "Fortran-FOSS-Programmers/FOODIE", - "url": "", - "categories": "numerical", - "tags": "ode pde euler runge kutta", - "license": "none" - }, - - { - "name": "fgsl", - "description": "Fortran interface to the GNU Scientific Library", - "github": "reinh-bader/fgsl", - "url": "", - "categories": "numerical interfaces", - "tags": "", - "license": "" - }, - - { - "name": "SciFortran", - "description": "collection of fortran modules and procedures for scientific calculations.", - "github": "aamaricci/SciFortran", - "url": "", - "categories": "numerical", - "tags": "", - "license": "" - }, - - { - "name": "Los Alamos Grid Toolbox (LaGriT)", - "description": "a library of user callable tools that provide mesh generation, mesh optimization and dynamic mesh maintenance", - "github": "lanl/LaGriT", - "url": "", - "categories": "numerical", - "tags": "", - "license": "BSD" - }, - - { - "name": "DBCSR", - "description": "Distributed block compresseed sparse row matrix library", - "github": "cp2k/dbcsr", - "url": "", - "categories": "numerical", - "tags": "linear algebra parallel mpi openmp cuda hip", - "license": "" - }, - - { - "name": "GALAHAD", - "description": "Modules for nonlinear optimization", - "github": "ralna/GALAHAD", - "url": "", - "categories": "numerical", - "tags": "least squares active set quadratic programming interior point convex programming linear programming", - "license": "GNU LGPL v3" - }, - - { - "name": "slsqp", - "description": "SLSQP nonlinear constrained optimizer", - "github": "jacobwilliams/slsqp", - "url": "", - "categories": "numerical", - "tags": "nonlinear programming equality inequality constraints", - "license": "none" - }, - - { - "name": "NumDiff", - "description": "a modern Fortran interface for computing the Jacobian (derivative) matrix of m nonlinear functions which depend on n variables", - "github": "jacobwilliams/NumDiff", - "url": "", - "categories": "numerical", - "tags": "finite difference", - "license": "none" - }, - - { - "name": "quaff", - "description": "Quantities for Fortran. Make math with units more convenient", - "github": "", - "url": "https://gitlab.com/everythingfunctional/quaff", - "categories": "numerical", - "tags": "", - "license": "MIT" - }, - - { - "name": "rng_fortran", - "description": "Pseudo random number generator in Fortran, internally using xoroshiro128+", - "github": "jannisteunissen/rng_fortran", - "url": "", - "categories": "numerical", - "tags": "uniform normal poisson distributed", - "license": "GNU GPL v3" - }, - - { - "name": "WRF", - "description": "Weather Research and Forecasting model", - "github": "wrf-model/WRF", - "url": "", - "categories": "scientific", - "tags": "", - "license": "Public domain" - }, - - { - "name": "fds", - "description": "Large-eddy simulation code for low-speed flows, with an emphasis on smoke and heat transport from fires.", - "github": "firemodels/fds", - "url": "", - "categories": "scientific", - "tags": "", - "license": "none" - }, - - { - "name": "Quantum ESPRESSO", - "description": "Quantum ESPRESSO is an integrated suite of Open-Source computer codes for electronic-structure calculations and materials modeling at the nanoscale", - "github": "QEF/q-e", - "url": "", - "categories": "scientific", - "tags": "electronic structure calculations quantum chemistry physics molecular dynamics mpi", - "license": "" - }, - - { - "name": "fluidity", - "description": "Computational fluid dynamics code with adaptive unstructured mesh capabilities", - "github": "FluidityProject/fluidity", - "url": "", - "categories": "scientific", - "tags": "cfd computational fluid dynamics unstructured", - "license": "" - }, - - { - "name": "fortran-machine", - "description": "", - "github": "mapmeld/fortran-machine", - "url": "", - "categories": "other", - "tags": "", - "license": "" - }, - - { - "name": "Nek5000", - "description": "MPI parallel higher-order spectral element CFD solver", - "github": "Nek5000/Nek5000", - "url": "", - "categories": "scientific", - "tags": "cfd computational fluid dynamics spectral element higher order mpi parallel les rans", - "license": "none" - }, - - { - "name": "cp2k", - "description": "quantum chemistry and solid state physics software package that can perform atomistic simulations", - "github": "cp2k/cp2k", - "url": "", - "categories": "scientific", - "tags": "quantum chemistry physics molecular dynamics metadynamics mpi cuda", - "license": "GNU GPL V2" - }, - - { - "name": "Castro", - "description": "An adaptive mesh, astrophysical radiation hydrodynamics simulation code", - "github": "AMReX-Astro/Castro", - "url": "", - "categories": "scientific", - "tags": "adaptive mesh astrophysics radiation hydrodynamics", - "license": "BSD 3-Clause" - }, - - { - "name": "QUIP", - "description": "The QUIP package is a collection of software tools to carry out molecular dynamics simulations.", - "github": "libAtoms/QUIP", - "url": "", - "categories": "scientific", - "tags": "electronic structure calculations quantum chemistry physics molecular dynamics mpi qm-mm", - "license": "GNU GPL V2" - }, - - { - "name": "ABINIT", - "description": "ABINIT is a software suite to calculate the optical, mechanical, vibrational, and other observable properties of materials", - "github": "abinit/abinit", - "url": "", - "categories": "scientific", - "tags": "electronic structure calculations quantum chemistry physics molecular dynamics mpi", - "license": "" - }, - - { - "name": "NASTRAN 95", - "description": "NASA Structural Analysis System, a finite element analysis program (FEA) completed in the early 1970's", - "github": "nasa/NASTRAN-95", - "url": "", - "categories": "scientific", - "tags": "finite element structural eigne stability loads", - "license": "none" - }, - - { - "name": "OFF", - "description": "Finite volume fluid dynamics", - "github": "szaghi/OFF", - "url": "", - "categories": "scientific", - "tags": "godunov riemann euler runge kutta structured", - "license": "GNU GPL v3" - }, - - { - "name": "freeCappuccino", - "description": "A three-dimensional unstructured finite volume code for fluid flow simulations.", - "github": "nikola-m/freeCappuccino", - "url": "", - "categories": "scientific", - "tags": "finite volume turbulent turbulence", - "license": "GNU GPL v3" - }, - - { - "name": "CaNS", - "description": "A code for fast, massively-parallel direct numerical simulations (DNS) of canonical flows", - "github": "p-costa/CaNS", - "url": "", - "categories": "scientific", - "tags": "fluid dynamics fluid simulation computational fluid dynamics turbulence high performance computing hpc cfd", - "license": "" - }, - - { - "name": "Truchas", - "description": "3D Multiphysics Simulation of Metal Casting and Processing", - "github": "truchas/truchas-release", - "url": "", - "categories": "scientific", - "tags": "fluid dynamics metal casting multiphysics hpc", - "license": "BSD 3-Clause" - }, - - { - "name": "dftatom", - "description": "Routines for Radial Integration of Dirac, Schrödinger, and Poisson Equations", - "github": "certik/dftatom", - "url": "", - "categories": "scientific", - "tags": "electronic structure calculations atomic", - "license": "MIT" - }, - - { - "name": "MESA", - "description": "Modules for Experiments in Stellar Astrophysics", - "github": "", - "url": "http://mesa.sourceforge.net/", - "categories": "scientific", - "tags": "stellar astrophysics", - "license": "GNU GPL V2" - }, - - { - "name": "Fortran 2018 examples", - "description": "Easy examples of scientific computing with modern, powerful, easy Fortran 2018 standard", - "github": "scivision/fortran2018-examples", - "url": "", - "categories": "examples", - "tags": "block coarray contiguous mpi namelist openmp random submodule iso_fortran_env", - "license": "GNU GPL V2" - }, - - { - "name": "Fortran patterns", - "description": "Popular design patterns implemented in Fortran", - "github": "farhanjk/FortranPatterns", - "url": "", - "categories": "examples", - "tags": "", - "license": "" - }, - - { - "name": "Numerical methods in fortran", - "description": "Solving linear, nonlinear equations, ordinary differential equations", - "github": "planelles20/numerical-methods-fortran", - "url": "", - "categories": "examples numerical", - "tags": "ode pde integral stochastic quadrature plotting", - "license": "" - }, - - ] \ No newline at end of file diff --git a/_site/packages/projects_search.js b/_site/packages/projects_search.js deleted file mode 100644 index bfcddfe02..000000000 --- a/_site/packages/projects_search.js +++ /dev/null @@ -1,154 +0,0 @@ -function findGetParameter(parameterName) { - // Return a GET HTTP parameter - var result = null, - tmp = []; - location.search - .substr(1) - .split("&") - .forEach(function (item) { - tmp = item.split("="); - if (tmp[0] === parameterName) result = decodeURIComponent(tmp[1]); - }); - return result; -} - -function getSubSentences(sentence) { - // Return all permutations of contiguous sub sentences from a sentence - var words = sentence.split(" "); - - var subs = []; - - var N = words.length; - - var i; - for (i = 1; i <= N; i++){ // Loop over possible sentence lengths - - var j; - for (j=0; j<=(N-i); j++){ // Loop over sentence locations - - sub_i = words.slice(j,j+i); - subs.push(sub_i.join(" ")); - - } - - } - - return subs; - -} - -function searchProjects(queryString,projects) { - // Basic sub-string matching within project fields - // - // Results ranked by size of matched sub-string and field weight - // - var subs = getSubSentences(queryString); - - // Sort by subsentence length descending - subs = subs.sort(function(a,b){return b.split(" ").length - a.split(" ").length}) - - var fields = ['name','description','tags','license','github','url']; - var fieldWeights = [10.0,1.0,1.0,0.1,1.0,0.1]; - - // Loop over projects JSON - var i; - for (i = 0; i 0){ - - project = results[i]; - - if (results[i].github != ""){ - out += '

    '; - out += ' '+project.name+'

    '; - } else { - out += '

    '; - if (project.url.includes('gitlab.com')) { - out += ' '; - } else if (project.url.includes('bitbucket.org')){ - out += ' '; - } - out += project.name+'

    '; - } - - out += '

    '+project.description; - - var cats = project.categories.split(" "); - out += ' (' - var j; - for (j=0;j'+cats[j]+''; - if (j'; - - } - - } - - return out; - -} - -// Perform search here onload -var queryString = findGetParameter('query').replace(/\+/g," ").replace(/"/g,''); -document.getElementById('search-query').value = queryString; - -results = searchProjects(queryString,projects); -resultsHTML = resultsToHTML(results); -document.getElementById('search-results').innerHTML = resultsHTML; \ No newline at end of file diff --git a/_site/packages/scientific.html b/_site/packages/scientific.html deleted file mode 100644 index c92ef4b69..000000000 --- a/_site/packages/scientific.html +++ /dev/null @@ -1,602 +0,0 @@ - - - - - - - - Scientific Codes - Fortran Programming Language - - - - - - - - - - - - - -

    - - -
    -

    Featured Open Source Projects

    -

    A rich ecosystem of high-performance code

    -
    - -
    -
    -
    - -

    Packages / - - - - Scientific Codes

    -

    - Applications and libraries for applied mathematical and scientific problems -

    - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -

    - - WRF

    - - - - - -
    - Weather Research and Forecasting model -
    - Tags: -

    - - fds

    - - - -
    - Large-eddy simulation code for low-speed flows, with an emphasis on smoke and heat transport from fires. -
    - Tags: -

    - - Quantum ESPRESSO

    - - - -
    - Quantum ESPRESSO is an integrated suite of Open-Source computer codes for electronic-structure calculations and materials modeling at the nanoscale -
    - Tags: electronic structure calculations quantum chemistry physics molecular dynamics mpi -

    - - fluidity

    - - - -
    - Computational fluid dynamics code with adaptive unstructured mesh capabilities -
    - Tags: cfd computational fluid dynamics unstructured -

    - - Nek5000

    - - - -
    - MPI parallel higher-order spectral element CFD solver -
    - Tags: cfd computational fluid dynamics spectral element higher order mpi parallel les rans -

    - - cp2k

    - - - - - -
    - quantum chemistry and solid state physics software package that can perform atomistic simulations -
    - Tags: quantum chemistry physics molecular dynamics metadynamics mpi cuda -

    - - Castro

    - - - - - -
    - An adaptive mesh, astrophysical radiation hydrodynamics simulation code -
    - Tags: adaptive mesh astrophysics radiation hydrodynamics -

    - - QUIP

    - - - - - -
    - The QUIP package is a collection of software tools to carry out molecular dynamics simulations. -
    - Tags: electronic structure calculations quantum chemistry physics molecular dynamics mpi qm-mm -

    - - ABINIT

    - - - -
    - ABINIT is a software suite to calculate the optical, mechanical, vibrational, and other observable properties of materials -
    - Tags: electronic structure calculations quantum chemistry physics molecular dynamics mpi -

    - - NASTRAN 95

    - - - -
    - NASA Structural Analysis System, a finite element analysis program (FEA) completed in the early 1970's -
    - Tags: finite element structural eigne stability loads -

    - - OFF

    - - - - - -
    - Finite volume fluid dynamics -
    - Tags: godunov riemann euler runge kutta structured -

    - - freeCappuccino

    - - - - - -
    - A three-dimensional unstructured finite volume code for fluid flow simulations. -
    - Tags: finite volume turbulent turbulence -

    - - CaNS

    - - - -
    - A code for fast, massively-parallel direct numerical simulations (DNS) of canonical flows -
    - Tags: fluid dynamics fluid simulation computational fluid dynamics turbulence high performance computing hpc cfd -

    - - Truchas

    - - - - - -
    - 3D Multiphysics Simulation of Metal Casting and Processing -
    - Tags: fluid dynamics metal casting multiphysics hpc -

    - - dftatom

    - - - - - - - -
    - Routines for Radial Integration of Dirac, Schrödinger, and Poisson Equations -
    - Tags: electronic structure calculations atomic -

    - - - MESA

    - - - - - -
    - Modules for Experiments in Stellar Astrophysics -
    - Tags: stellar astrophysics -
    - -
    - -
    -
    - -
    -
    -
    - - - See - - here for how to get your project listed. - -
    -
    - - - - - - - - - - - - - diff --git a/_site/packages/search/index.html b/_site/packages/search/index.html deleted file mode 100644 index 32b7a8016..000000000 --- a/_site/packages/search/index.html +++ /dev/null @@ -1,174 +0,0 @@ - - - - - - - - Search - Fortran Programming Language - - - - - - - - - - - - - - - - - - - -
    -
    -
    - -

    Packages / Search

    - -
    - - -
    -
    - -
    - -
    - -
    -
    - -
    -
    -
    - - - See - - here for how to get your project listed. - -
    -
    - - - - - - - - - - - - - - diff --git a/_site/packages/strings.html b/_site/packages/strings.html deleted file mode 100644 index 04f3c13bc..000000000 --- a/_site/packages/strings.html +++ /dev/null @@ -1,312 +0,0 @@ - - - - - - - - Characters and strings - Fortran Programming Language - - - - - - - - - - - - - - - - -
    -

    Featured Open Source Projects

    -

    A rich ecosystem of high-performance code

    -
    - -
    -
    -
    - -

    Packages / - - - - Characters and strings

    -

    - Libraries for manipulating characters and strings -

    - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -

    - - coretran

    - - - -
    - Core fortran routines and object-oriented classes for sorting, kD-Trees, and other algorithms to handle scientific data and concepts -
    - Tags: dynamic array formatting debugging errors kdtree sorting random binary search strings unit testing timing -

    - - StringiFor

    - - - -
    - Fortran strings manipulator -
    - Tags: split join basename search concat -

    - - M_strings

    - - - -
    - Fortran string manipulations -
    - Tags: upper lower quoted join replace white space string conversion tokens split -

    - - - - - Strings for Fortran

    - - - -
    - A library of string functions for Fortran. -
    - Tags: -

    - - - - - iso_varying_string

    - - - -
    - Implementation of the Fortran ISO_VARYING_STRING module in accordance with the standard -
    - Tags: varying length character strings -
    - -
    - -
    -
    - -
    -
    -
    - - - See - - here for how to get your project listed. - -
    -
    - - - - - - - - - - - - -