Skip to content

Commit

Permalink
Merge pull request #1 from ipqa-research/groups
Browse files Browse the repository at this point in the history
Groups
  • Loading branch information
fedebenelli authored Apr 3, 2024
2 parents 1ca415b + ce16bef commit 810a0b0
Show file tree
Hide file tree
Showing 9 changed files with 121 additions and 20 deletions.
2 changes: 1 addition & 1 deletion .vscode
8 changes: 8 additions & 0 deletions example/main.f90
Original file line number Diff line number Diff line change
@@ -1,8 +1,11 @@
program main
use forsus, only: Substance, forsus_dir

use forsus_properties_groups, only: Groups

type(Substance) :: sus(2)
character(len=50) :: only_this(3)
type(Groups) :: group

forsus_dir = "data/json"

Expand All @@ -22,4 +25,9 @@ program main
print *, sus(1)%critical%critical_temperature%units
print *, sus(1)%critical%critical_volume%units

call group%from_json("UnifacVLE", "1-butanol.json")

print *, group%ids
print *, group%counts

end program
2 changes: 1 addition & 1 deletion src/forsus.f90
Original file line number Diff line number Diff line change
Expand Up @@ -4,5 +4,5 @@ module forsus
use forsus_properties
use forsus_substance

character(len=*), parameter :: version = "0.1.0"
character(len=*), parameter :: version = "0.1.1"
end module
36 changes: 31 additions & 5 deletions src/properties/base.f90
Original file line number Diff line number Diff line change
Expand Up @@ -10,17 +10,17 @@ module forsus_properties_base
character(len=:), allocatable :: units !! Units
contains
procedure(abs_from_json), deferred :: from_json
end type
end type Property

abstract interface
impure elemental subroutine abs_from_json(self, name, json_str, path)
!! How a Property reader routine is espected to work.
!!
!! A Property should be setted up by providing it's name and a
!! A Property should be setted up by providing it's name and a
!! `json` file relative (or absolute) path. The Property instance
!! name should be setted up inside the subroutine and later on
!! the Property value(s) should be read from the `json` file.
!!
!!
!! Inside the subroutine the default `forsus_dir` path should be used
!! but it should also be possible to use an optional custom path.
!!
Expand All @@ -30,6 +30,32 @@ impure elemental subroutine abs_from_json(self, name, json_str, path)
character(len=*), intent(in) :: name !! Property's name (`json` key)
character(len=*), intent(in) :: json_str !! `json` file path
character(len=*), optional, intent(in) :: path !! Optional database path
end subroutine
end subroutine abs_from_json
end interface
end module

contains
function open_json(json_str, path) result(json)
use iso_fortran_env, only: error_unit
use json_module, only: json_file
use forsus_constants, only: forsus_default_dir, forsus_dir
type(json_file) :: json
character(len=*), intent(in) :: json_str
character(len=*), optional, intent(in) :: path

call json%initialize()

if (present(path)) then
call json%load_file(path//"/"//json_str)
else
if (allocated(forsus_dir)) then
call json%load_file(forsus_dir//"/"//json_str)
else
call json%load_file(forsus_default_dir//"/"//json_str)
end if
end if
if (json%failed()) then
write(error_unit, *) "ERROR: Invalid .json file: ", json_str
error stop 1
end if
end function open_json
end module forsus_properties_base
47 changes: 47 additions & 0 deletions src/properties/group.f90
Original file line number Diff line number Diff line change
@@ -0,0 +1,47 @@
module forsus_properties_groups
use forsus_properties_base, only: Property, open_json

type, extends(Property) :: Groups
!! Groups for a group-contribution based method.
integer, allocatable :: ids(:)
integer, allocatable :: counts(:)
contains
procedure :: from_json
end type Groups
contains
impure elemental subroutine from_json(self, name, json_str, path)
!! From a json file and a model name set the present groups.
use json_module, only: json_array, json_file
class(Groups), intent(in out) :: self !! Groups
character(len=*), intent(in) :: name !! Model name
character(len=*), intent(in) :: json_str !! `json` file
character(len=*), optional, intent(in) :: path !! Path to file

type(json_file) :: json
integer :: i, id, count
logical :: found
character(len=:), allocatable :: base, str
character(len=50) :: idx

! Initialize empty arrays
allocate(self%ids(0))
allocate(self%counts(0))

json = open_json(json_str, path)

base = name//".group("

i = 1
do
write(idx, *) i
str = base // trim(adjustl(idx)) // ")"
call json%get(str // ".id", id, found=found)
call json%get(str // ".value", count, found=found)
if (.not. found) exit

self%ids = [self%ids, id]
self%counts = [self%counts, count]
i = i+1
end do
end subroutine from_json
end module forsus_properties_groups
1 change: 1 addition & 0 deletions src/properties/properties.f90
Original file line number Diff line number Diff line change
Expand Up @@ -2,4 +2,5 @@ module forsus_properties
!! Possible properties defined in the package.
use forsus_properties_scalar, only: ScalarProperty
use forsus_properties_critical_constants, only: CriticalConstants
use forsus_properties_groups, only: Groups
end module
9 changes: 3 additions & 6 deletions src/properties/scalar_property.f90
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
module forsus_properties_scalar
use forsus_constants, only: pr, forsus_default_dir, forsus_dir
use forsus_properties_base, only: Property
use forsus_properties_base, only: Property, open_json
use json_module, only: json_file
implicit none

Expand Down Expand Up @@ -29,6 +29,8 @@ impure elemental subroutine scalar_from_json(self, name, json_str, path)
type(json_file) :: json

self%name = name

json = open_json(json_str, path)
call json%initialize()

if (present(path)) then
Expand All @@ -41,11 +43,6 @@ impure elemental subroutine scalar_from_json(self, name, json_str, path)
end if
end if

if (json%failed()) then
write(error_unit, *) "ERROR: Invalid .json file: ", json_str
error stop 1
end if

call json%get(self%name//".value(1)", self%value)
call json%get(self%name//".units", self%units)
end subroutine scalar_from_json
Expand Down
20 changes: 13 additions & 7 deletions src/substance.f90
Original file line number Diff line number Diff line change
@@ -1,5 +1,5 @@
module forsus_substance
use forsus_properties, only: ScalarProperty, CriticalConstants
use forsus_properties, only: ScalarProperty, CriticalConstants, Groups
implicit none

type :: Substance
Expand Down Expand Up @@ -65,6 +65,8 @@ module forsus_substance
!! Parachor
type(ScalarProperty) :: mathiascopeman(3)
!! Mathias Copeman \(\alpha\) function parameters
type(Groups) :: unifac_vle
!! UNIFAC-VLE model groups
end type

! Setting this interface allows to use `init_json` as the object init
Expand All @@ -85,16 +87,20 @@ type(Substance) function init_json(name, path, only)
!! Only extract this parameters, the options are:
!!
!! - "critical": Tc, Pc and Acentric Factor


character(len=:), allocatable :: file
integer :: i

init_json%name = trim(name)
file = init_json%name // ".json"

if (.not. present(only)) then
call init_json%parachor%from_json("Parachor", init_json%name//".json", path)
call init_json%mathiascopeman(1)%from_json("MatthiasCopemanC1", init_json%name//".json", path)
call init_json%mathiascopeman(2)%from_json("MatthiasCopemanC2", init_json%name//".json", path)
call init_json%mathiascopeman(3)%from_json("MatthiasCopemanC3", init_json%name//".json", path)
call init_json%critical%from_json(init_json%name//".json", path)
call init_json%parachor%from_json("Parachor", file, path)
call init_json%mathiascopeman(1)%from_json("MatthiasCopemanC1", file, path)
call init_json%mathiascopeman(2)%from_json("MatthiasCopemanC2", file, path)
call init_json%mathiascopeman(3)%from_json("MatthiasCopemanC3", file, path)
call init_json%unifac_vle%from_json("UnifacVLE", file, path)
call init_json%critical%from_json(file, path)
else
do i=1,size(only)
select case(only(i))
Expand Down
16 changes: 16 additions & 0 deletions test/test.f90
Original file line number Diff line number Diff line change
Expand Up @@ -32,6 +32,8 @@ subroutine test_values
call test(1.3327_pr, sus%mathiascopeman(1)%value, "MathiasCopemanC1")
call test(0.96946_pr, sus%mathiascopeman(2)%value, "MathiasCopemanC2")
call test(-3.1879_pr, sus%mathiascopeman(3)%value, "MathiasCopemanC3")
call test_int([1, 2, 15], sus%unifac_vle%ids, "UNIFAC-VLE ids")
call test_int([1, 1, 1], sus%unifac_vle%counts, "UNIFAC-VLE counts")
end subroutine

subroutine test_critical
Expand All @@ -54,6 +56,20 @@ subroutine test(value, calc_value, name)
print *, "Ok!"
end if
end subroutine

subroutine test_int(value, calc_value, name)
integer, intent(in) :: value(:)
integer, intent(in) :: calc_value(:)
character(len=*), intent(in) :: name

write (*, "(A)", advance="no") name
if (maxval(abs((value - calc_value)/value)) > tolerance) then
print *, "Error!"
error stop 1
else
print *, "Ok!"
end if
end subroutine

subroutine test_failed_read
integer :: exitstat, cmdstat
Expand Down

0 comments on commit 810a0b0

Please sign in to comment.