Compiling the original Matlab

On Windows, one can compile the original Matlab code from 1982 on GitHub with Intel Fortran, gfortran, or g95 with the default options and get an executable in 5 seconds. One excludes s.for from the list of files to be compiled since that is the main program for VAX/VMS. The main program for MS-DOS is in sys.for. For g95, running the created executable gives

  < M A T L A B >
Version of 05/25/82

 HELP is available

 <>
At line 23 of file PRNTID.FOR (Unit 0)
Traceback: not available, compile with -ftrace=frame or -ftrace=full
Fortran runtime error: Expected CHARACTER for item 1 in formatted transfer, got INTEGER.  If you want to make character descriptors typeless, compile with -fsloppy-char
(1X,8(4A1,2H  ))
    ^

Compiling with -fsloppy-char as suggested, the program just prints <> down the screen and does not allow input. This happens when compiling with gfortran and Intel too.

Any suggestions to make the program work?

Matlab has been a very successful program. Rewriting the original Matlab in modern Fortran and extending it could be an interesting project.

6 Likes

This is great, I didn’t know the original Matlab’s source code was available!

2 Likes

I’ve compiled the 1988 version before, which is archived by @urbanjost at the link matlab88. It was quite fascinating to see it working.

6 Likes

Thanks. On Windows it compiles and runs with any of

g95 matlab88.f -fsloppy-char
gfortran -std=legacy -fallow-invalid-boz matlab88.f
ifort matlab88.f

Personally, I would like to see some bright young person with more free time than
I have write some modern Fortran work-alikes (probably as a stdlib project) of some
of th useful Matlab array/matrix utilities that I would love to see as an intrinsic part
of Fortran. The goal would be improve Fortran’s array and matrix capabilites and make
translating Matlab code to Fortran much easier. Two in particular are the Matlab unique
and find functions. I’ve created my own versions of these but they only support a small
subset of the Matlab functions capability I needed at the time. Other functions I’ve implemeted are linspace, chol, std, mean, sub2ind, and ismember. I’m guessing others in the community have implemented these or other Matlab functions over the years.

An even more ambitious project would be to implement a standard set of interfaces for the most commonly used linear algebra functions that hide the calls to whatever library you link in (LAPACK, MKL LAPACK, IMSL etc) behind a standard interface. I’ve always wondered why Fortran didn’t have intrinsic linear system solvers etc along the lines of x=B\A as part of the language. With over 50 years worth of research in numerical linear
algebra, I think we know by now what methods are the best for most applications. Not having to write logic to handle the different interfaces used by different packages would be a major additon to the language IMHO. Since Fortran already has a distributed data structure (co-arrays), parallel solvers such as SCALAPACK etc could also be supported.

Another advantage of adding more Matlab like functions to Fortran is it would make it easier for current generations of engineering (and I guess other majors) students whose only exposure to programming might be Matlab to ease into Fortran. I’ve always said that one of the major reasons people moved away from Fortran is the lack of anything like the STL or Numpy/Scipy that gives you things for free that Fortran unfortunately forces you to write yourself. stdlib is a big step in this direction.

Speaking for myself, I think one of the goals for future versions of Fortran should be to make Fortran Matlab’s older but still faster and smarter brother. So who is up for writing iso_matlab_extensions and iso_linear_algebra modules.

7 Likes

Got it compiled and running with Microsoft FORTRAN PowerStation 32 1.0 for Win NT:

matlab

4 Likes

matlab88.f also compiles and runs on Linux (Mint 19.3) with Intel oneAPI ifort (v 2021.1).

1 Like

The free source form version by Jacob Williams compiles and runs on Windows with gfortran, g95, and Intel Fortran.

1 Like

Hmm … there was a “Work In Progress” that might be of interest to anyone interested in the base matlab-like functionality.

It uses some other modules, so it has to be used with fpm:
M_matrix

download the github repository and build it with
fpm ( as described at Fortran Package Manager )

     git clone https://github.com/urbanjost/M_matrix.git
     cd M_matrix
     fpm run

or just list it as a dependency in your fpm.toml project file.

        [dependencies]
        M_matrix        = { git = "https://github.com/urbanjost/M_matrix.git" }

M_matrix is a module that should not require using as many legacy features that has a primitive interface allowing it to be called as a subroutine from a Fortran program that can use the same input, initially based on the old matlab routines.

Have not had time to work on the original project concept, but the idea was to emulate the function of a private module (M_inspect) that I find “indispensible” that lets you pass data in and out of your main program via a procedure call with a mini-matlab-like interface, to plot it, save it as matlab and octave input files, CSV and NAMELIST files, do a numeric “diff” of values against saved templates of data, and many other functions that are useful for debugging, development,inspection and unit testing.

M_matrix is just a prototype of the “matab-like” interface component I was toying with creating for an Open version but If there is interest, we can polish up the calling interface enough for others to work with it but I do not foresee having any time soon to do more than that myself right now.

M_matrix only had a few “legacy” issues remaining before it would be a very portable module; albeit needing some restructuring where I last left it.

There is a manpage for the mat88() procedure and a sample program (mat(1)) that go with M_matrix in there.

???

@rwmsu, that is precisely the goal of the stdlib project, at least from my perspective. We keep adding functions and we look into Matlab, Python/SciPy, Julia, etc. Yes, we want to have good linear algebra, as well as the other functions you mentioned. You can browse the open issues here:

e.g.:

If you would be interested in helping us out, we would really appreciate it. We are all very busy and not much free time, but the good news is that in open source if we all just put in a little bit of time, that is enough. I can help you get started, just let me know!

1 Like

Here is a subroutine to list the unique values of an array and optionally their frequencies, adapted from code of the Degenerate Conic. Ideally there would be options to sort the unique values or to sort by their frequencies. For large vectors it would be more efficient to sort the input data before finding unique values.

module unique_mod
implicit none
contains
subroutine unique(vec,vec_unique,freq)
! Return the unique values from vec and optionally their frequencies
integer, intent(in)                         :: vec(:)
integer, intent(out), allocatable           :: vec_unique(:) ! (nuniq) unique values
integer, intent(out), allocatable, optional :: freq(:)       ! (nuniq) corresponding frequencies, if PRESENT
integer                                     :: i,num(size(vec)),nuniq
logical                                     :: mask(size(vec))
mask = .false.
do i=1,size(vec)
    num(i) = count(vec(i) == vec) ! count the number of occurrences of this element:
    if (num(i)==1) then ! there is only one, flag it:
        mask(i) = .true.
    else
        if (.not. any(vec(i)==vec .and. mask)) mask(i) = .true. ! flag this value only if it hasn't already been flagged:
    end if
end do
! return only flagged elements:
nuniq = count(mask)
allocate(vec_unique(nuniq))
vec_unique = pack(vec,mask)
if (present(freq)) then
   allocate (freq(nuniq))
   freq = pack(num,mask)
end if
end subroutine unique
end module unique_mod   

program main
use unique_mod, only: unique
implicit none
integer, allocatable :: unq(:),freq(:),freq_chk(:)
integer, parameter   :: n = 100
real                 :: x(n)
integer              :: i,iran(n),nuniq
character (len=*), parameter :: fmt_i = "(100(i0,1x))"
! small test case
call unique([3,1,1,5],unq,freq)
print*,unq
print*,freq
! larger test case
call random_seed()
call random_number(x)
iran = nint(100*x)
call unique(iran,unq,freq)
nuniq = size(unq)
write (*,fmt_i) unq
write (*,fmt_i) freq
allocate (freq_chk(nuniq))
freq_chk = [(count(iran==unq(i)),i=1,nuniq)]
write (*,fmt_i) freq_chk
print*,"should be zero:",sum((freq-freq_chk)**2),sum(freq)-n
end program main

Sample output:

   3           1           5
   1           2           1
34 0 87 24 2 83 95 22 45 55 63 43 94 52 79 25 37 32 9 67 77 5 96 82 11 17 86 13 93 47 15 8 66 92 20 27 30 65 57 72 21 1 71 73 59 54 90 10 91 7 38 50 29 99 81 89 12 39 56 76 70
2 1 4 1 2 2 2 1 3 2 2 3 2 3 3 1 1 1 1 1 1 1 1 2 4 2 1 1 2 2 1 1 1 1 2 1 2 2 2 1 1 4 1 1 3 1 2 2 1 1 1 1 2 1 2 1 2 1 1 1 1
2 1 4 1 2 2 2 1 3 2 2 3 2 3 3 1 1 1 1 1 1 1 1 2 4 2 1 1 2 2 1 1 1 1 2 1 2 2 2 1 1 4 1 1 3 1 2 2 1 1 1 1 2 1 2 1 2 1 1 1 1
 should be zero:           0           0
1 Like

@Beliavsky

I do something similar but sort a copy of the input array first. qsort is my quick sort
code and almostEqual is an generic name for elemental functions that test real
values to some spacing increment.

  Subroutine uniqueR64(x,u)
    USE global_constants, ONLY: IK, REAL64
    Implicit NONE
    Real(REAL64), Intent(IN)               :: x(:)
    Real(REAL64), ALLOCATABLE, Intent(OUT) :: u(:)
    Integer(IK)  :: i, nx, nu
    Real(REAL64) :: ut(SIZE(x,1))
    Logical      :: iu(SIZE(x,1))
    nx = SIZE(x,1)
    ut = x
    Call qsort(ut,1,nx)
    iu = .TRUE.
    Do i=2,nx
      If (AlmostEqual(ut(i),ut(i-1))) iu(i) = .FALSE.
    End Do
    nu = COUNT(iu.EQV..TRUE.)
    ALLOCATE(u(nu))
    u = PACK(ut, (iu.EQV..TRUE.))
  End Subroutine uniqueR64

  Elemental Function almostEqual64(a, b) Result(aeqb)
! Function to test if two REAL64 floating point numbers 
! almost equal to close to machine precision 

! Code taken from post on Intel Fortran Forum 11/15/2016
    Implicit NONE
! Argument variables
    Real(REAL64), Intent(IN) :: a, b
    Logical                  :: aeqb
! default value of SPACING_FACTOR64 = 5.0_REAL64
    aeqb = ABS(a-b) < SPACING_FACTOR64*SPACING(MAX(ABS(a), ABS(b)))
  End Function almostEqual64
1 Like

If the linalg and similar procedures like these unique functions were in an fpm(1) package I could eliminate half the code in M_matrix (hint, hint). I Actually have a version of M_matrix now that allows for decently passing data in and out of a user program that is closer to the original intent of the original LA matlab version which I will probably put on the github site this week. It is certainly not going to compete with matlab/octave/R/mathematica … but I am finding it useful when working with Fortran for everything from non-hierarchical configuration files to creating quick unit tests even though it is nowhere near done. If no one else is interested I plan on making it more “Fortran-ish” as I have no intent of turning it into a language, but simply a Fortran tool, so do not expect it to stay upward-compatible with it’s current form.

But some of the uses I have been making of the M_matrix code got me thinking about LFortran,

Is there any plan for LFortran to be callable via an API from Fortran code compiled with other compilers? It looks like it will support the opposite direction, but I was wondering if I had a main program compiled with another compiler that I could not or did not want for sundry reasons to compile with LFortran could I “call” Lfortran and pass data to and from it? Since Fortran does not expose it’s data easily even something like putting something in my program like “call pass_to_Lfortran(X,name=‘mydata’)” would be interesting, I am picturing that I could “call” Lfortran and use Lfortran interactively to examine and manipulate the data, Looking forward to using Fortran interactively again (there used to be several F77 interpreters, which I think are all gone now) especially now that Fortran is so much more powerful.

1 Like

LFortran is really just a C++ library, so we can easily expose it in Fortran itself also. I guess it could be an fpm package then. We got 3 GSoC students for it and we plan to get first users this summer and to compile roughly Fortran 95 codes. Our idea was that there would be many “modes” how you can call LFortran (as an lfortran binary, from C++, from Python, from Fortran per your suggestion, as a Jupyter kernel, perhaps more directly called from fpm so the Fortran wrappers would be helpful, etc.). This will get figured out naturally as the community starts using it more.

3 Likes