Deformation Monitoring Package (DMPACK)

Greetings,

in the past three years, I have used Fortran extensively in my research, particularly, in engineering geodesy and automated deformation monitoring. Following a prototype in Python, the Deformation Monitoring Package (DMPACK) is both a software library and a collection of programs for sensor control and time series processing in geodesy and geotechnics, written in Fortran 2018.

While still being in development, I’d like to present this project as an example of general-purpose programming in modern Fortran. Essentially, DMPACK is a collection of codes to build autonomous sensor networks in the so called “Internet of Things”, and to monitor terrain, slopes, construction sites, or objects like bridges, tunnels, dams, heritage buildings, and so on, by analysing time series collected from geodetic and geotechnical sensors (like, total station, GNSS, MEMS, inclinometer, RTD, …).

The package seeks to cover common tasks encountered in contemporary deformation monitoring, and it already features:

  • sensor control (USB, RS-232/422/485, 1-Wire, file system, sub-process),
  • sensor data parsing and processing,
  • database access and synchronisation,
  • data serialisation (ASCII, CSV, JSON, JSON Lines, Fortran Namelist),
  • inter-process communication and message passing,
  • remote procedure calls via HTTP-RPC API,
  • distributed logging,
  • Lua scripting,
  • time series plotting and report generation,
  • Atom web feeds for log messages (XML/XSLT),
  • web user interface,
  • MQTT connectivity,
  • e-mail.

At the current stage, DMPACK consists of 74 modules, 22 programs, and 32 test programs. The whole source tree, including the required ISO_C_BINDING interface modules solely written for this project (to POSIX, SQLite 3, libcurl, PCRE2, Lua 5.4, zlib), counts > 34,000 SLOC in Fortran, spread over 160 source files.

The schema of the DMPACK client–server architecture:

I admit, the package is not incredibly interesting for the non-geodetic audience, but let me give you a brief overview of two aspects that might be worthwhile for other Fortran coders.

HTTP-RPC API

Fortran is not only used to communicate with sensors and actors, but also for HTTP-based Remote Procedure Calls (RPCs) between client and server, for instance, to collect time series and log messages from remote sensor nodes. My approach is nothing special and widely used elsewhere, nevertheless, it works reliable, even in Fortran:

  1. Let’s say, an arbitrary sensor is connected through RS-232. On Unix, the serial port is mapped to one of the TTY devices, such as /dev/ttyS0. The sensor control program of DMPACK sends requests periodically to the sensor, reads the sensor’s responses, and extracts the measurement values from each raw response using the passed regular expression pattern (PCRE2).

  2. The observation data is forwarded via a POSIX messages queue to DMPACK’s database program which will store it in a local SQLite database (after validation).

  3. The sync program synchronises the local database with a remote server by using a simple RPC mechanism:

    • An observation is read from database into a Fortran derived type. The derived type is serialised to Fortran 95 Namelist format.

    • The character string of the Namelist representation is deflate compressed (zlib) and sent to the remote server via HTTP POST (libcurl). Compression is optional, but reduces the payload size from around 40 KiB to less than 4 KiB in the best case, and allows a transmission rate of up to 50 observations per second (locally). But there is still some room for optimisations (maybe, by using a binary IDL format, concurrency, HTTP/2 or WebSockets).

    • Authentication is provided by the web server (HTTP Basic Auth), which is sufficient in this scenario. The authentication backend can be easily upgraded to LDAP if required. The HTTP-API does some basic authorisation, too. All connections are generally TLS-encrypted.

    • The RPC server, also written in Fortran, and running behind FastCGI, accepts the request, inflates the compressed data (zlib again), reads the Namelist into a derived type, and, after validation, stores the observation in the server database.

    • If no error occured, the client program marks the observation as synchronised, and repeats the above steps for all observations that have not been successfully transmitted yet.

Additionally, the time series stored in the server database can be accessed through the same HTTP-RPC API. Authenticated users may download observations or logs from arbitrary sensor nodes in CSV, JSON, or JSON Lines format.

Web UI

One of the problems I’ve stumbled upon is the question of how to provide a graphical user interface to configure servers and sensor nodes, and to display time series, logs, and handshake messages. As we all know, GUIs are not a strength of the Fortran eco-system.

As the sensor nodes are usually deployed in remote locations, some kind of web interface seems to be preferable. (The Tk toolkit would be another decent fit, but running X11 on an “embedded device” + using session forwarding is certainly a little to heavy for those little machines – not taking into account the reality of poor mobile internet connections and high latency.)

For me, the implementation of a user interface is more of a burden than strictly necessary. I would be fine with a text-based UI over SSH, but that won’t win any prizes nowadays. At the end, I’ve just put some constraints on my approach:

  • Cross-Environment: The web-based user interface must be able to run on (embedded) sensor nodes and servers alike, as both connect to the same database backend. And I’m not going to write two damn web applications.

  • No JavaScript: Not just because it would mean introducing another programming language, but also because text-based browsers (such as elinks or w3m) do not have support for JS in general, and I’d like to access the web interface within an SSH session just in case. And without JS, there is no AJAX, no REST, no SPA cretinism. Certainly, it keeps the architecture simple.

  • Semantic Web: Straight forward and mostly class-less HTML5, a single CSS file, no sophisticated web design. I’ve settled for classless.css which covers all the HTML elements I need (I really appreciate it when people more talented with all this web clobber share their work under a permissive licence).

  • Code Reuse: Most of the required functionality is already covered by the DMPACK library in one way or another. Using any other language than Fortran would force me to re-implement large portions of the code base, or to provide an additional C API (just the database abstraction layer over SQLite is > 4,000 SLOC in Fortran …). I guess, the most sensible decision here is therefore to just stick with Fortran and accept the limitations.

The skills needed to write web applications in Fortran are probably not in high demand by today’s software industry. However, that does not imply it would be impossible or nonsensical. The Common Gateway Interface (CGI) standard is around for decades (the first draft specification was published in 1993) – and still works flawlessly in “modern” web environments. The protocol is trivially simple, which is why we can write CGI applications in nearly every (serious) programming language.

I’m quite an adherer of CGI and it’s definitely a choice that gets results displayed very quickly if you cannot or don’t want to use one of the “real” web frameworks the cool kids on that Orange Site are talking about, but polishing the small details can turn quite cumbersome in Fortran, and the modest requirements of CGI come at a cost:

  • Each request starts a new process, i.e., some CPU load can be expected, but we’re not talking about 10,000 users per hour here. Another disadvantage is the start-up time of a CGI application in contrast to the persistent processes of FastCGI/SCGI. But modern operating systems are not stupid, and continuous program invocations are usually cached.

  • Traditionally, CGI demands one application per route/endpoint, but we can overcome this limitation by implementing a basic URL router (how hard can that be in Fortran?).

  • Templating is rather ugly in Fortran, especially, without a proper templating engine. I’ve settled for hard-coded HTML markup and some string templating, hidden behind library procedures that return formatted and encoded strings (I hope that won’t hurt my street credibility too much).

So, my approach is rather old-school, and, I can imagine, seen as legacy, but again, the goal is just to provide some kind of database gateway to display time series and graphs that is guaranteed to work in 15 or 20 years from now (try that with React!).

The result is a classic CGI program, executed by lighttpd, that consumes GET and POST requests, does some basic routing, and returns HTML5. The performance is okayish, I guess?: an HTTP response from the DMPACK web UI usually takes around 50 msecs (remotely deployed; locally it’s < 20 msecs). When plotting a graph of 1,000 observations, the response time increases to 150 msecs (< 50 msecs locally). I don’t know how long modern web applications take to render, but these results are acceptable by my standards.

By the way, it just requires some Unix IPC magic to create decent looking graphs for the web in Fortran:

  • The web interface provides a simple HTML form for the user to select sensor node, sensor, time range of the observations to plot, and so on. The form data is then submitted to the CGI application via HTTP POST.

  • After form validation, the Fortran program fetches the time series from database, opens Gnuplot in a new process, connects stdin and stdout of the process with pipes, and finally writes plot commands and time series to Gnuplot’s stdin.

  • Gnuplot returns the plot in SVG format through stdout. The XML is read from the pipe, Base64-encoded, and pasted as a data-uri directly into the src attribute of the HTML <img> tag. The HTML page, including the encoded SVG, is then returned as a single response to the client. If activated, the web server additionally compresses the response (gzip).

For a few thousand observations, SVG is an appropriate choice. Since the SVG format just contains XML-encoded primitives, the size of an SVG file grows linearly with every additional data point. Alternatively, we could use one of Gnuplot’s raster image terminals instead (like, PNG), but these depend on Xlib and some other dependencies (for which I don’t have the space for on embedded sensor nodes), while SVG is solely text-based.

Screen Shot of Web UI

Conclusion

So, was it worth to undertake this endeavour in Fortran? Well, you know the old saying: we do this not because it is easy, but because we thought it would be easy. The software is quite an improvement in comparison to the Python prototype, but that was to be expected.

POSIX system calls (serial comm., date and time functions, IPC, message passing, …) are obviously MUCH easier in C/C++ or through some abstraction layer. Getting this right took many weeks. And with the new JSON capabilities of SQLite, the bulky derived-type-to-JSON converters in Fortran were superfluous in retrospect.

Hopefully, Fortran will excel once I dive deeper into the time series analysis part of my project (that was the original intention to use Fortran in the first place). For now, I’m satisfied with the outcome, even if an implementation in C + Tcl would have saved me at least a year of development time that was required to write the necessary interface bindings for Fortran. But here we are.

Cheers!

25 Likes

This is a really interesting project. Can this system run on some very low-power computer? Such as those “single board PC”-type machines? I believe this kind of system could be very useful for many kinds of remote monitoring applications. I’m thinking a sensor node network for building automation, etc.

Would it be possible to somehow send information/commands from the web UI into the sensor device? I can imagine some sensor device might have GPIO pin(s) for driving a relay coil for turning the lights (or any other device) on/off, for example.

1 Like

Those are the primary target of the client software. I’ve not tested DMPACK on ARM-based boards yet, but I’m confident that it will run, as the programs have only modest hardware requirements. Actually, I have been using single-board computers (Raspberry Pi 2) running an alpha version ( :see_no_evil:) of FreeBSD 11 and the Python prototype to conduct permanent deformation monitorings of two German Autobahn bridges since 2016 with success. I even added a backup system – that was never needed.

Photo of one of the sensor nodes

But it has also demonstrated why Python is the wrong environment for such software: while single-board computers might not have an exceptional amount of computing power, even the older models feature multiple cores. As you probably know, Python cannot take much advantage of them due to GIL. And you certainly don’t want to descent to the Edge of Hell that Python’s multi-processing world is.

Not at the moment. The jobs to perform (i.e., what commands to send to sensors) are currently read from an evaluable configuration file, but a job database + synchronisation is on the to-do list.

4 Likes

Track the surface of any volcanoes with this? Add some GPS and elevation information and tracking trucks and sensing potholes and ocean currents could be next. I think you covered everything else :slight_smile: . Great project. A very enjoyable read.

2 Likes

The endeavour was certainly worth it for the Fortran community.

I believe the large number of bindings you provided in this context
(I did not know that many of them are related to your actual PhD project)
has really been very useful for the Fortran community and also served
as an inspiration for further projects (I am thinking of the Fortran HTTP client).

I wish you much success for the remaining parts of your project.

4 Likes

That’s really really impressive work; congrats, Philipp! The scope is jaw-dropping to me.

Do you think components of DMPACK could be extracted to package a dedicated web framework for Fortran? Of course, one could just take DMPACK and use only pieces of it, but the domain-specific components that would not be generally needed do carry a complexity cost.

Let’s please not use such words, even only to describe technologies. REST was somebody’s PhD thesis and much of modern infrastructure relies on it (just like it does on Fortran) (and by the way REST has nothing to do with JS). SPA solves a specific and real problem that other web technologies don’t. It’s sufficient to write that you don’t like these technologies, if you don’t.

Should be doable pretty easily. Just copy the modules dm_cgi and dm_router, optionally dm_fcgi (requires FastCGI DevKit), and replace the prefix with something sensible. If you want to read requests with binary payload, you’ll need fortran-unix additionally as a dependency, or, simply provide an interface to read(2). For a real web framework, some kind of template parsing could be added. The modules dm_mime and dm_html are probably too specific to be used in a general-purpose web library.

Maybe, I should have marked by snarky comments as tongue-in-cheek. Unfortunately, Roy Fielding shares the fate of Herbert D. Benington (the father of the Waterfall model), whose works are often misunderstood. The original idea was pretty great: serve small snippets of web content and put everything together on client side, with libraries like intercooler.js for the browser. No need for Server-Side Includes and countless Perl/PHP scripts just to mix content. However, when people speak of REST and RESTful APIs today, they often mean JSON-RPC, which, combined with SPA and cargo culting, tends to lead to awful results that nobody wants to touch in two years from now. I just wanted to say that SPA, despite the on-going hype, is not always the right choice.

About two years later, a lot of progress has been made with the development of DMPACK. The project grew from 34,000 to 65,000 SLOC, from 74 to 112 library modules, and from 22 to 30 programs. Some of the additions are visible in the new schematic overview:

For the new features, further ISO C binding interfaces have been released to gain access to third-party C libraries from Fortran:

Perhaps, they’re useful for other folks out here.

I tried to compile the most interesting project changes in the following sections.


ARM Platform

After some modifications to the POSIX and SysV interface library fortran-unix, DMPACK now runs on the AArch64 platform as well (either Linux or FreeBSD). 64-bit ARM chipsets are available for single-board computers (e.g., Raspberry Pi 4 series), Edge systems (e.g., Siemens SIMATIC series), and IoT Gateways with 4G/5G connectivity (e.g., MOXA UC-2200A series), which are all more suitable for being used as sensor nodes than generic computers based on x86-64, I would argue.

Camera Capture

Well, this is still early stage. Generally, the monitoring system handles only observations of discrete phenomena which can be expressed as 8-byte real values. The next version of DMPACK will hopefully feature the continuous or periodical capture of camera images, for instance from webcams (V4L2) or IP camera streams (RTSP).

The part covering the camera access is finished already and handed to FFmpeg, the image transmission to the server still must be done. For now, we can capture images of a USB camera attached to /dev/video0 and add a timestamp to the lower left corner with GraphicsMagick:

character(len=*), parameter :: IMAGE_PATH = '/tmp/image.jpg' ! Output image.

integer                :: rc       ! Return code.
type(camera_type)      :: camera   ! Camera record.
type(gm_text_box_type) :: text_box ! GraphicsMagick text box.

call dm_init()

! Capture image.
camera = camera_type(input  = '/dev/video0', &
                     device = CAMERA_DEVICE_V4L2, &
                     width  = 1280, &
                     height = 720)
rc = dm_camera_capture(camera, IMAGE_PATH)
call dm_error_out(rc)

! Add text box.
text_box = gm_text_box_type(font='DroidSansMono', font_size=16)
rc = dm_gm_add_text_box(IMAGE_PATH, text=dm_time_now(), text_box=text_box)
call dm_error_out(rc)

I’ve tested it with a cheap Logitech webcam and with the webcam of my ThinkPad, works both on Linux and FreeBSD. To capture a still image from the RTSP stream of an IP camera, we just have to change input path and device type of the camera:

camera = camera_type(input='rtsp://10.10.10.15:8554/camera1', device=CAMERA_DEVICE_RTSP)

System Monitoring

As the system resources of sensor nodes are limited, an eye should be kept on certain parameters, like:

  • system uptime,
  • load averages,
  • free disk space,
  • database size, or
  • CPU temperature.

In general, one would use syslog on Unix-like operating systems for this, but such a service requires the set-up of a dedicated logging infrastructure. The monitoring system already handles the transmission and storage of suitable data structures: observations and logs, i.e., system parameters may be turned into observations and events into log messages.

Two abstractions were necessary, one for Linux and one for FreeBSD, unified in a generic interface at build-time. The library then reads system parameters from /proc (Linux) or uses pipes to call standard command-line utilities, such as sysctl or vmstat (FreeBSD). Once stored in the database, the time series can be plotted and exported like any other observations.

character(len=*), parameter :: PATH = '.' ! Current directory.

character(len=256) :: model, name, paths(2)
integer            :: capacity, ncore
integer(kind=i8)   :: available, size, used
real               :: avgs(3), temp

! Read free disk space (sizes in bytes).
rc = dm_system_disk_free(PATH, paths(1), size, used, available, capacity, paths(2))
rc = dm_system_cpu_cores(ncore)                        ! Read CPU cores.
rc = dm_system_cpu_model(model)                        ! Read CPU model.
rc = dm_system_cpu_temperature(temp)                   ! Read CPU temperature (if available).
rc = dm_system_load_average(avgs(1), avgs(2), avgs(3)) ! Read load averages (1, 5, 15 min).
rc = dm_system_host_name(name)                         ! Read host name.

print '(" Path...........: ", a)',          PATH
print '(" File system....: ", a)',          trim(paths(1))
print '(" Mounted on.....: ", a)',          trim(paths(2))
print '(" Size...........: ", a)',          dm_size_to_human(size)
print '(" Used...........: ", a)',          dm_size_to_human(used)
print '(" Available......: ", a)',          dm_size_to_human(available)
print '(" Capacity.......: ", i0, " %")',   capacity
print '(" CPU model......: ", a)',          trim(model)
print '(" CPU cores......: ", i0)',         ncore
print '(" CPU temperature: ", f0.1, " C")', temp
print '(" CPU load.......:", 3(1x, f0.2))', avgs
print '(" Host name......: ", a)',          trim(name)

Solar Power & Battery Monitoring

In my day job, I was given the task to build two sensor nodes with off-grid power supply based on solar appliances made by Victron Energy. PV panels and batteries are connected to a Maximum Power Point Tracking (MPPT) solar charger that meters the power generation of the panels. Reading the state of charge of the battery bank requires an additional battery monitor unit. Both, MPPT charger and battery monitor, offer a simple TTL hardware interface and output various parameters through the VE.Direct protocol once per second, among them:

  • panel and battery voltage and current,
  • amount of produced and consumed energy,
  • yield and maximum power,
  • state of charge and battery temperature,
  • number of charge cycles,
  • mid-point deviation of the battery bank.

I’ve implemented a basic state machine in Fortran to parse the VE.Direct protocol byte-by-byte. The following snippet creates a single VE.Direct block from a sequentially readbyte, adds it to a frame, and converts the frame to a response type once finished:

character           :: byte                 ! Single byte.
integer             :: rc                   ! Return code.
logical             :: eor, finished, valid ! Flags.
type(ve_frame_type) :: frame                ! VE.Direct data frame.
type(response_type) :: response             ! Response record.

do
    call read_byte(byte)
    call dm_ve_frame_next(frame, byte, eor, finished, valid)

    if (finished) then
        if (valid) then
            print '("Checksum is valid")'
        else
            print '("Checksum is invalid")'
        end if

        call dm_ve_frame_reset(frame)
        exit
    end if

    if (eor) then
        call dm_ve_frame_read(frame, response)
        print '("Name: ", a, " Value: ", f8.1)', response%name, response%value
    end if
end do

The response could be added to an observation and stored in the database. The program dmved covers all the device communications, parsing, and message passing, turning solar charger and battery monitor into sensors (see schematic overview at the top).

HTML & PDF Reports

A report generator dmreport was added to the project for creating HTML documents with inline plots of time series and an optional log message table. The HTML markup of the document is simply generated from pre-defined constants and some utility functions, and then written to file.

Screen Shot

Additionally, output in PDF format may be desired. There are tools available to convert HTML documents to PDF, but the results do not look satisfying IMHO. I first thought about creating LaTeX markup to make PDF reports, but TeXLive and TinyTeX are quite heavy in size and dependencies. So, I gave troff (the standard Unix typesetting system) a look and went further to write an abstraction module over GNU roff in Fortran. At the moment, only the ms and tbl macro packages are supported. For example, to create a PDF document from ms markup:

character(len=:), allocatable :: roff ! GNU roff markup.
integer                       :: rc   ! Return code.

call dm_init()

! Generate markup with macro package -ms.
roff = dm_roff_ms_header(title='Test Report', author='Sensor Node 1', &
                         institution='University of Elbonia',         &
                         font_family=ROFF_FONT_HELVETICA,             &
                         left_footer=dm_time_date(),                  &
                         right_footer='DMPACK ' // DM_VERSION_STRING)
roff = roff // dm_roff_ms_sh(2, 'Results')
roff = roff // dm_roff_ms_lp('First paragraph.')

! Create PDF from markup.
rc = dm_roff_to_pdf(roff, 'report.pdf', macro=ROFF_MACRO_MS)

The generated markup string is piped to GNU roff, typesetted to PostScript, and finally converted to the PDF file report.pdf. The document may also include plots made with Gnuplot:

Screen Shot

You probably recognise the distinct troff look.

All in all, using troff instead of LaTeX was the right choice, and the whole Fortran module for markup generation is just 440 SLOC.

10/10 – would use again

SQL Query Builder

Once the database abstraction layer grew to a certain size, a basic SQL query builder was needed to not rewrite the same code sections over and over, just to generate custom SQL queries. The db_query module allows to add SET, WHERE, ORDER BY, and LIMIT parameters to an SQL base query. The following example creates a SELECT query to read the last observation id from SQLite database observ.sqlite:

character(len=:), allocatable :: node_id, observ_id, sensor_id, target_id
character(len=:), allocatable :: sql

integer             :: rc  ! Return code.
type(db_type)       :: db  ! Database.
type(db_query_type) :: dbq ! Database query.
type(db_stmt_type)  :: dbs ! Database statement.

call dm_init()

! Query parameters.
node_id   = 'dummy-node'
sensor_id = 'dummy-sensor'
target_id = 'dummy-target'

! Open an existing observation database first.
rc = dm_db_open(db, 'observ.sqlite', read_only=.true.)
call dm_error_out(rc, fatal=.true.)

! Set SQL base query string.
call dm_db_query_set_sql(dbq,                                      &
    'SELECT observs.id FROM observs '                           // &
    'INNER JOIN nodes ON nodes.row_id = observs.node_id '       // &
    'INNER JOIN sensors ON sensors.row_id = observs.sensor_id ' // &
    'INNER JOIN targets ON targets.row_id = observs.target_id')

! Set WHERE clause of the query.
call dm_db_query_where(dbq, 'nodes.id = ?',   node_id)
call dm_db_query_where(dbq, 'sensors.id = ?', sensor_id)
call dm_db_query_where(dbq, 'targets.id = ?', target_id)

! Set ORDER BY and LIMIT of the query.
call dm_db_query_set_order(dbq, by='observs.timestamp', desc=.true.)
call dm_db_query_set_limit(dbq, 1_i8)

! Create full query string from base query.
sql = dm_db_query_build(dbq)

sql_block: block
    ! Prepare the database statement.
    rc = dm_db_prepare(db, dbs, sql)
    if (dm_is_error(rc)) exit sql_block

    ! Bind the query parameters to the statement.
    rc = dm_db_bind(dbs, dbq)
    if (dm_is_error(rc)) exit sql_block

    ! Run the statement.
    rc = dm_db_step(dbs)
    if (rc /= E_DB_ROW) exit sql_block

    ! Get next row as allocatable character string.
    rc = dm_db_row_next(dbs, observ_id)
    if (dm_is_error(rc)) exit sql_block
end block sql_block

call dm_error_out(rc, verbose=.true.)
call dm_db_query_destroy(dbq)
call dm_db_finalize(dbs)
call dm_db_close(db)

if (allocated(observ_id)) print '("observ_id: ", a)', observ_id

In retrospect, the query builder could have been written in OOP style, but the implemented procedural API will do it for now.

Chat Bot

The client–server architecture (or, Edge Cloud, how it is called nowadays) of the project expects sensor node units to work autonomously and to forward any data (observations, logs, handshakes) to a central monitoring server, which means that there is no interface, except for SSH and HTTP, to interact with the sensor nodes in real-time.

I was searching for an easy approach to send arbitrary commands to an internet-connected remote sensor node to query status and health statistics, something like, you know, a chat app. The sorry state of chat protocols in 2025 makes XMPP/Jabber still the first choice when it comes to instant messaging. It’s feature-complete, well tested, and, in comparison, low on resources, while IRC is too limited (short text messages only), Signal/Telegram/Slack are all proprietary, Matrix is too complex and lacks a decent C library, and MQTT has no real eco-system for the use-case.

Implementing a chat bot based on XMPP inevitably means to descend to XML hell, but the libstrophe library takes at least some of the pain from us. The first step was to write proper ISO C interface bindings to libstrophe. Then, an abstraction module for DMPACK followed, that provides a more simple XMPP API. Finally, the chat agent dmbot based on the module was written. At the current stage, the bot supports only a few commands to ask for its status and to create log messages. Later versions are planned to offer access to the sensor node database and returning captured camera images on demand.

Sending commands to the dmbot instance of a sensor node, using Psi:

Deutscher Wetterdienst API

Deutscher Wetterdienst (DWD) is the federal meteorological service of Germany and provides free weather data online. I thought it would be an easy task[1] to add a Fortran module to the library in order to access the DWD open data API, fetch weather reports recurrently, and store selected observations to database.

But since it’s a service of a German agency, the interfaces and data formats are all arcane. If you have ever worked with open data from, let’s say, U.S. National Weather Service or GeoSphere Austria, you’re up to a time travel to the 1990s. Even the DWD open data platform just greets visitors with an auto-generated “index of” page …[2]

After digging through a documentation consisting mostly of PDF files and Excel sheets, and playing some advanced Stackenblochen, I was able to download weather reports through an HTTP GET request to the DWD server by reusing the HTTP-RPC API:

type(dwd_weather_report_type), allocatable :: reports(:)

call dm_init()

! Send HTTP request.
block
    character(len=:), allocatable :: url      ! Open data API endpoint.
    integer                       :: rc       ! Return code.
    type(rpc_request_type)        :: request  ! HTTP request.
    type(rpc_response_type)       :: response ! HTTP response.

    ! Initialise RPC backend and create scratch file.
    rc = dm_rpc_init()
    open (action='readwrite', form='formatted', newunit=response%unit, status='scratch')

    ! Generate URL of DWD open data API and send HTTP GET request.
    url = dm_dwd_api_weather_report_url(station_id='10385', tls=.false.)
    rc  = dm_rpc_get(request, response, url, callback=dm_dwd_api_callback)

    ! Read weather reports from response in scratch file.
    rewind (response%unit)
    rc = dm_dwd_weather_report_read(reports, response%unit)

    ! Clean-up.
    close (response%unit)
    call dm_rpc_destroy(request)
    call dm_rpc_destroy(response)
    call dm_rpc_shutdown()
end block

! Output data.
block
    integer :: i

    ! Print date, time, and ground temperature of weather reports.
    do i = 1, size(reports)
        associate (report => reports(i))
            if (.not. dm_dwd_weather_report_has_value(report%temperature_5cm)) cycle
            print '(a, " T: ", f5.1, " °C")', dm_time_to_human(report%timestamp, zone=.false.), &
                                              report%temperature_5cm
        end associate
    end do
end block

The URL of the weather reports file is created from the id of a particular weather station (10385 is Airport Berlin–Brandenburg). The CSV-like report is written to a scratch file first, then parsed and splitted into the array reports. Optionally, the RPC API allows us to send an If-Modified-Since HTTP header when polling reports, which saves us some unnessary network traffic.

Since station id querying might come handy at some point, I’ve also added an abstraction layer over the MOSMIX station catalog. The catalog is just a column-oriented text file containing all active and inactive weather stations known to DWD:

MOSMIX Station Catalog
ID    ICAO NAME                 LAT    LON     ELEV
----- ---- -------------------- -----  ------- -----
01001 ENJA JAN MAYEN             70.56   -8.40    10
01008 ENSB SVALBARD              78.15   15.28    29
01025 ---- TROMSOE               69.41   18.55    10
01028 ENBJ BJORNOYA              74.31   19.01    16
01049 ENAT ALTA LUFTHAVN         69.59   23.22     3
01052 ENHF HAMMERFEST            70.40   23.40    81
01059 ENNA BANAK/LAKSELV (AFB)   70.04   24.59     8
01089 ENKR KIRKENES              69.44   29.54    91
01092 ---- MAKKAUR FYR           70.43   30.04     9
01112 ENBN BRONNOYSUND/BRONNOY   65.27   12.13     8
01149 ---- BASMOEN               66.20   14.06    34
01152 ENBO BODOE                 67.16   14.22    13
01180 ---- HARSTAD               68.48   16.32    45
01194 ---- NARVIK                68.28   17.30    17
01210 ENAL ALESUND AIRP          62.34    6.07    22
01215 ---- HJELVIG (MYRBO)       62.37    7.14    35
01223 ENKB KRISTIANSUND          63.07    7.50    44
01238 ---- FOKSTUA 2             62.07    9.17   973
01241 ENOL ORLAND                63.42    9.36     7
01271 ENVA TRONDHEIM             63.28   10.55    17
...

The Fortran API won’t win any beauty contests:

character(len=*), parameter :: CATALOG    = 'catalog.cfg' ! MOSMIX station catalog.
character(len=*), parameter :: STATION_ID = '10385'       ! Airport Berlin-Brandenburg.

integer :: rc, stat, unit
logical :: found

type(dwd_mosmix_station_type)              :: station
type(dwd_mosmix_station_type), allocatable :: stations(:)

call dm_init()

! Read MOSMIX station catalog from file into array.
open (action='read', file=CATALOG, iostat=stat, newunit=unit, status='old')
if (stat /= 0) call dm_error_out(E_NOT_FOUND, fatal=.true.)
rc = dm_dwd_mosmix_station_catalog_read(stations, unit)
close (unit)

! Search for station by id.
rc = dm_dwd_mosmix_station_find(stations, STATION_ID, station, found)
if (.not. found) call dm_error_out(rc, fatal=.true.)

! Output station data.
call dm_dwd_mosmix_station_out(station)

That’s all for now. Maybe my post could give you some inspiration on what is possible in modern Fortran. Cheers!


  1. oh, boy ↩︎

  2. Not so long ago, the service was still based on FTP – the Internet, Germany’s uncharted waters. Yikes. ↩︎

5 Likes