Here’s a more specific (imaginary) example.
Imagine we are developing a blood measurement device, and our partner company provides us with a module to register blood samples and store them in a database:
module blood_sample_registry
implicit none
public
integer, parameter :: rk = kind(1.0e0)
type :: blood_sample
integer :: id
character(2), private :: blood_type
real(rk), private :: sodium
real(rk), private :: hematocrit
end type
interface
module function register_sample(blood_type,sodium,hematocrit) result(sample)
character(2), intent(in) :: blood_type
real(rk), intent(in) :: sodium, hematocrit
type(blood_sample) :: sample
end function
module subroutine write_sample(fileunit,sample)
integer, intent(in) :: fileunit
type(blood_sample), intent(in) :: sample
end subroutine
end interface
end module
program blood_device
use blood_sample_registry
implicit none
type(blood_sample) :: sample
integer :: database
sample = register_sample( &
blood_type='AB', &
sodium=130., &
hematocrit=40.1)
open(newunit=database,file="blood_database.txt",access='stream')
call write_sample(database,sample)
close(database)
end program
Someone who happens to come across the database file, could easily run it through a hexdump:
$ hexdump -C blood_database.txt
00000000 01 00 00 00 41 42 00 00 02 43 66 66 20 42 02 00 |....AB...Cff B..|
00000010 00 00 30 30 00 00 07 43 66 66 14 42 |..00...Cff.B|
0000001c
It’s easy enough to notice the AB
and 00
symbols. A minute later the malevolent person runs a $ grep -nr "blood_sample"
, and is quickly able to locate a left-over module source file which was unsuccessfully deleted after installation. Using the type definition, the person can easily decode the whole thing:
print *, transfer(int(z'0001'),1)
print *, achar(int(z'41')), achar(int(z'42'))
print *, transfer(int(z'43020000'),1.0)
print *, transfer(int(z'42206666'),1.0)
end
1
BA
130.000000
40.0999985
The quote from MRC that submodules can help conceal implementation secrets is only valid for procedures. Derived-type components however, are left exposed. They need to be hidden within a separate derived type.
Full example
!> Hidden
module blood_private
implicit none
integer, parameter :: rk = kind(1.0e0)
type :: blood_sample_private
! Members should be public if we don't want to use getters
character(2) :: blood_type
real(rk) :: sodium
real(rk) :: hematocrit
end type
end module
!> Visible to clients for integration in blood measurement devices
module blood_sampler
use blood_private, only: rk, blood_sample_private
implicit none
private
public :: blood_sample, register_sample, write_sample, rk
type :: blood_sample
integer :: id
type(blood_sample_private), private :: data
end type
interface
module function register_sample(blood_type,sodium,hematocrit) result(sample)
character(2), intent(in) :: blood_type
real(rk), intent(in) :: sodium, hematocrit
type(blood_sample) :: sample
end function
module subroutine write_sample(fileunit,sample)
integer, intent(in) :: fileunit
type(blood_sample), intent(in) :: sample
end subroutine
end interface
end module
!> Submodule is not shared, but provided precompiled as a shared library
!>
submodule (blood_sampler) blood_sampler_actions
contains
! how we assign ID's, how we validate sample values should be hidden
! so no one can tamper with it without having to disassemble the binary objects
module function register_sample(blood_type,sodium,hematocrit) result(sample)
character(2), intent(in) :: blood_type
real(rk), intent(in) :: sodium, hematocrit
type(blood_sample) :: sample
integer, save :: id = 0
id = id + 1
sample%id = id
sample%data = blood_sample_private(blood_type,sodium,hematocrit)
end function
module subroutine write_sample(fileunit,sample)
integer, intent(in) :: fileunit
type(blood_sample), intent(in) :: sample
write(fileunit) sample%id, &
sample%data%blood_type, &
sample%data%sodium, &
sample%data%hematocrit
end subroutine
end submodule
program blood_laboratory
use blood_sampler
implicit none
type(blood_sample) :: sample(2)
integer :: database
sample(1) = register_sample( &
blood_type='AB', &
sodium=130., &
hematocrit=40.1)
sample(2) = register_sample( &
blood_type='00', &
sodium=135., &
hematocrit=37.1)
open(newunit=database,file="blood_database.txt",access='stream')
call write_sample(database,sample(1))
call write_sample(database,sample(2))
close(database)
end program