TweetFollow Us on Twitter

FORTRAN to Mach2
Volume Number:5
Issue Number:3
Column Tag:Forth Forum

Porting FORTRAN to Mach 2

By Jörg Langowski, MacTutor Editorial Board

“Mach2 and FORTRAN”

Regular readers of this column will have noticed that for my work on machines other than the Mac, I often use Fortran. Also, you’ll have remarked that I’ve complained a lot about the complications that arise when one wants to do even the simplest matrix operations in Forth; keeping track of three loop levels for array indexing just goes beyond the capabilities of the average human. There is just no elegant way to deal with multi-dimensional arrays in Forth so far (please: if you object to that, do send me your implementation, and I’ll promise to print it!).

Now, there exist a lot of ready-written Fortran subroutines that do matrix inversion, solution of linear equations, diagonalization, least-squares fitting and more complicated things. Many of those routines exist in the source libraries of mainframe computers at universities and research institutions, and often they are even in the public domain. Also, although most scientific software is still written in Fortran, there is a wealth of good implementations available in Pascal and C. Alas, not so much luck with Forth. There are specific math packages for some Forth implementations, not yet for Mach2 to my knowledge; but wouldn’t it be nice to have some generic way of including external subroutines to Mach2 programs, be they written in Fortran, Pascal, C, or assembler?

This column describes a utility that does exactly what we want: given an external routine in a resource file, with the entry point at the start of the code, it will read the resource and compile it into the Mach2 code. All we have to know is the number of parameters that the routine expects. This utility also serves me as an excuse to speak about the (excellent) MPW Fortran implementation by Language Systems, which I received some months ago.

The external code resource linker

Lets assume we have a Pascal routine that expects three parameters on the stack. For clarity, all parameter are supposed to be longints. On entry to the routine, the stack looks like in Fig.1.

Fig.1: param. setup for Pascal procedure call

We have already seen many examples how to write Mach2 routines that look like Pascal procedures to the Mac, for instance MDEFs or dialog filter procedures. This time we are going to do the opposite, calling a procedure from Mach2 that is written in Pascal or conforms to the Pascal parameter passing standard. Language Systems Fortran subroutines use that standard, so we’ll be able to call our Fortran routines that way.

Before we jump to the entry point of the external routine, we have to setup the A7 stack as shown in Fig. 1. The ‘external procedure linker’ automatically creates the glue code for moving the parameters from the Forth to the A7 stack and pushing the correct return address on the stack.

The principle of the method is as follows: If you want to link the external procedure ‘myProc’ into Forth code being compiled, you first open a resource file that contains a PROC resource with the name of your routine ‘myProc’:

\1

“ myResFile” call OpenResFile 
\ you may store the refno returned by OpenResFile 
\ somewhere, so that you can easily close the file later

and then you write:

: my.definition
 ( does some stuff )

 par1 par2 par3 [ ExtProc 3 myProc ]

 ( does some more stuff )
;

This code sequence will tell the external procedure linker to setup the A7 stack for 3 longint parameters and the return address, then copy the code found in the resource PROC name ‘myProc’ into the Mach2 code space. The return address references the code that starts after the loaded code; this reference is automatically resolved.

The program (Listing 1) also provides support for functions which return a longint result; such function must reside in FUNC resources in the resource file and are compiled by writing

 [ ExtFunc #pars myFunc ]

The only difference is that one longint zero is pushed to the A7 stack before pushing the parameters.

Fortran parameter passing

LS Fortran allows to pass parameters by value when calling other routines (see below), but the subroutines themselves expect all parameters to be passed by reference. Therefore the stack setup is very simple; only 32-bit addresses are passed. When we call Fortran routines from Mach2, we must therefore always put the addresses, not the values of variables on the stack.

Read listing 1 for the Mach2 source of the external linker. At the beginning you’ll also find a definition for a different sort of do loop, ?do next, which allows a loop to be skipped altogether when the initial value of the loop index is greater that the index limit. We need that definition for creating the code that takes the parameters off the Forth stack and pushes them on the A7 stack.

Language Systems’ Fortran for MPW

Let’s now digress a little and look at LS Fortran in more detail. The compiler is an MPW tool; by typing

fortran filename [options]

one creates an object file that can be linked with the Fortran libraries, all the existing MPW libraries or Pascal or C procedures. A typical mainframe Fortran program contains I/O statements for keyboard input and terminal output. The code generated from such a program will have support for a standard ‘glass teletype’ I/O window. And, most surprising: when your program stops, the glass teletype stays on the screen and becomes a TextEdit window; the program output can be reviewed, edited, and saved to a file. All the support code for standard I/O, text editing and file saving is automatically loaded with the Fortran code when any reference is made to the Fortran I/O library (such as a WRITE (unit,format) iolist statement).

I was very impressed by this Fortran implementation by the way it supports standard I/O in a way almost transparent to the Macintosh programmer. Of course you don’t need this support for a ‘real’ Macintosh program, and it takes about 50K of code; just use only the toolbox for I/O, no Fortran I/O statements, and the code won’t be linked in.

Arrays larger than 32K are supported; any time a routine uses a local variable space of more than 16K, a heap object will be allocated for the local variables whose size is only limited by the memory of the Macintosh. Common blocks, too, are stored in the heap. Initialization and disposal of the heap objects is automatically done at the beginning and the end of the program.

Large array and Common support, too, will link large segments of code from the run time library, notably the error handler which uses the glass teletype output window; therefore, in a ‘pure Macintosh’ program, you can’t use big arrays by simply defining them in your subroutine. However, since LS Fortran also supports structures, pointers and handles, there is a very easy way to circumvent this restriction. The example is given in listing 2, subroutine bigarray. We define an array as a structure with one field, an indexed integer*4:

 structure /array/
 integer*4 f(1)
 end structure

and reference this structure through a handle. Pointer and handle definitions are given in an include file that comes with the Fortran system. For our example, they look like the following:

 structure /Parray/
 pointer /array/ P
 end structure
 
 structure /Harray/
 pointer /Parray/ H
 end structure

 record /Harray/ myarray

After going through this setup, we can reference our indexed data field f through double indirection:

myarray.h^.p^.f(i)

will return the value of the i-th element of the array. Multi-dimensional arrays can be set up in an analogous way. The only thing that remains is to make the array handle reference some legal memory space. This is done through a toolbox call, e.g.

 j = newHandle(%val(arraysize*4))
 if (j.ne.0) then 
 myarray.h = j
 end if

This code sequence also gives you an idea how Macintosh toolbox routines are called; their names are made known to the compiler by including the line

!!M Inlines.f

at the beginning of the source file; Inlines.f is a file that contains inline toolbox routine definitions. [The Fortran system contains an MPW tool for updating that file in case new toolbox routines are released. Very nice.] The toolbox routine is called using call when it is defined as a Pascal procedure and like a Fortran function if it is defined as a function in Inside Mac.

Note that you have to indicate explicitly when a parameter has to be passed by value, as in NewHandle(%val(handlesize)), the default being call by reference. Not including %val in toolbox calls has got me confused several times - be careful to check your calls thoroughly.

LS MPW Fortran supports 68020 and 68881 code generation; I have run no extensive benchmarks, but it makes my MacII run at about 40-50% the speed of a Microvax II for typical programs. This should improve by at least a factor of two if Language Systems gets their act together and include a reasonable optimizer in their compiler. The version 1.0 that I have will accept the -opt=n compiler directive on the command line, but the code generated looks the same no matter what optimization level is used and it is certainly less than optimal, with lots of unnecessary transfers back and forth between local variables and registers. In fact, I was rolling on the floor laughing when I saw the first assembly listing. I called LS after I found out, thinking I was too stupid to activate the optimizer, but they admitted that selecting the optimizer has no effect in version 1.0 and that it should change with the next version. They should at least say something about that in the manual. Still I think it is a very good Fortran implementation; some of my Vax programs required some work on minor syntax differences, but in general the transport was easy. A working program can be easily made to run in the background on the Mac by strategic placement of some calls to WaitNextEvent; all of a sudden the MacII becomes a serious competitor for a mini-mainframe. The optimizer will - hopefully - come.

Listing 2 contains several example subroutines that we shall later call from Mach2. They range from simple extended-to-real floating point conversions to a Gauss-Jordan algorithm for the solution of a system of linear equations. Please look at the code for more details; we don’t have enough space to describe it all here.

The !!S compiler directive indicates the segment name into which the code will be placed, the same as the resource name later used by ExtProc. Listing 3 contains an MPW script for generating a resource file with the PROC resources, and for building a Fortran application that tests the Gauss-Jordan and matrix multiplication routines by solving a system of linear equations.

The end of the Forth example (listing 1) contains words which call the external Fortran routines. You see a definition of single-to-extended floating point conversions, a routine that computes the distance between two points in 3-d space, a program that creates a large array on the heap, uses it and disposes the heap object, and finally the linear equation testing program, analogous to the Fortran application. These latter two programs are included as applications on the source code disk; also included is the ‘machsub’ file with the PROC resources, in case you want to test this code from Mach2 but don’t have the Fortran compiler. The PROC resources have been compiled with the 68020 and 68881 options off, so they should work on any Mac.

The approach described here should work equally well with external routines written in other languages, and notably it should be easy to add dynamic run time linking support. One simply would have to reserve memory and load the PROC resource in as it is needed. You are welcome to experiment and share your experiences in this column.

Till next month.

Listing 1: Mach2 external code resource linker 

\ external code resource linker
\ to be used for linking in external subroutines
\ syntax
\ : <forth word>
\[ ExtProc 3 mySub ] ( gets resource PROC “mySub”& links it )
\       ( 3 parameters required )
\[ ExtFunc 3 myFnc ] ( gets resource FUNC “myFnc” & links it)
\     ( 3 parameters required, placeholder for function result )
\ ;
\
\ The external procedure loader follows Pascal calling 
\ conventions, i.e.,
\ it will put one longint/parameter and return address on top 
\ of the A7 stack. Return is made to the code directly 
\ following the loaded 
\ external procedure, just as you would expect.
\
\ © 1989 J. Langowski / MacTutor

only forth also mac also assembler

 \ taken with permission from Mach2 roundtable on GEnie - JL
 \
 \ An example of writing new looping structure,  ?DO ... NEXT.
 \ Acts like a DO ... LOOP except that the test for loop 
 \ completion is done before the loop body is executed, thus
 \ if the ?DO “limit” is less than or equal to starting “index”
 \ loop body will be skipped (remember that a DO ... LOOP will
 \ always execute loop body at least once, even if the starting
 \ index equals the limit).  Waymen @ PASC  

 ASCII ?DO_  CONSTANT ?DOMark

 : ?DO  ( limit index -- ) \ compile time  ( -- )
     STATE @
     IF
         $26C526C6 ,    ( MOVE.L  D5,(A3)+
                          MOVE.L  D6,(A3)+ )
         $2C1E2A1E ,    ( MOVE.L  (A6)+,D6
                          MOVE.L  (A6)+,D5 )
         $6000 W,       ( BRA )
      HERE  >R  0 W, \ space for forward branch offset 
         ?DOMark >R     \ compiler flag
     ELSE
         -1  ABORT” Compile only!”
     THEN ; IMMEDIATE

 : NEXT  ( -- )
 \ compile time ( -- )
     STATE @ IF
  R> ?DOMark = IF
             $5286 W,       ( ADDQ.L #1,D6)
             HERE R@  -  R@ W!  \ patch forward branch left by ?DO
             $BA86 W,       ( CMP.L  D6,D5 )
             R>  HERE  -   \ backward branch offset for BGT
             $6E00  W, W,   ( BGT )  
             $2C232A23 ,    ( MOVE.L  -(A3),D6
                              MOVE.L  -(A3),D5 )
         ELSE
             -1 ABORT” Unpaired ?DO”
         THEN
     ELSE
         -1 ABORT” Compile only!”
     THEN ; IMMEDIATE

\ ------------------------------------------
\ external procedure linker code starts here
\ ------------------------------------------

$20 constant bl
variable subrfile 

: pushA6 $2F1E w, ;
: push0 $2F3C w, 0 , ;
: popA6 $2D1F w, ;
: pushret $41FA0000 , \ LEA 0(PC),A0
 $2F08 w, \ MOVE.L A0,-(A7)
 here 4-\ address of PC reference
;

: ExtProc { | procHdl retAddr -- }
 bl word number? IF ( # params OK )
 0 ?DO pushA6 NEXT
 pushret
 ascii PROC bl word call GetNamedResource
 ?dup IF -> procHdl
 procHdl @ here procHdl call SizeRsrc 
 dup allot ( procPtr here size )
 cmove \ move code into Forth object space
 here over - swap w! \ resolve LEA reference
 ELSE abort” ExtProc - can’t find routine”
 THEN
 ELSE abort” ExtProc - parameter number syntax error”
 THEN
;

: ExtFunc { | procHdl retAddr -- }
 bl word number? IF ( # params OK )
 push0 \ space for function result
 0 ?DO pushA6 NEXT
 pushret
 ascii FUNC bl word call GetNamedResource
 ?dup IF -> procHdl
 procHdl @ here procHdl call SizeRsrc 
 dup allot ( procPtr here size )
 cmove \ move code into Forth object space
 here over - swap w! \ resolve LEA reference
 popA6
 ELSE abort” ExtProc - can’t find routine”
 THEN
 ELSE abort” ExtProc - parameter number syntax error”
 THEN
;

\ --------------------------------------------------
\ define some calls to external (Fortran) procedures
\ --------------------------------------------------

“ machsub” call openresfile subrfile !

: x2r [ extproc 2 x2r ] ;
: r2x [ extproc 2 r2x ] ;

: distance ( p q r | -- )
 [ extproc 3 distance ]
;
variable myarrayH
variable myarraysize

: makearray ( arrayhandle arraysize -- )
 [ extproc 2 makearray ]
;
: gaussj ( a n np b m mp ierr -- )
 [ extproc 7 gaussj ]
;
: matmul ( a b c n np m mp l lp -- )
 [ extproc 9 matmul ]
;
subrfile @ call closeresfile

\ --------------------------------------------------
\ end of external definitions; testing routines
\ --------------------------------------------------

also sane fp
fvariable x 20 vallot
fvariable y 20 vallot
fvariable dist 

: f>s { | [ 6 lallot ] x s -- }
 ^ x f! \ store from FP stack into local variable
 ^ x ^ s x2r
 s
;
: s>f { s | [ 6 lallot ] x -- }
 ^ s ^ x r2x
 ^ x f@ \ push local variable to FP stack 
;
: setup.x.y
 1.5 x f!  2.5 x 10 + f!  3.5 x 20 + f!
 3.5 y f! -1.0 y 10 + f!  0.0 y 20 + f!
;

: compute.distance
 x y dist distance
 cr .” The distance between points x and y is “
 dist f@ f. .” units” cr
;

: test.array
 cr .” Setting up 10000 element array...” cr
 10000 myarraySize !
 myarrayH myarraySize makearray
 .” Testing setup: “ cr
 10000 0 DO
 .” array(“ i . .” ) = “ myarrayH @ @ i 4* + @ . cr
 1000 +loop
 myarrayH @ call disposhandle drop
;

5 constant maxdim 

variable n variable n1 
variable m variable m1 
variable ierr 

variable a maxdim dup * 4* 4- vallot ( np*np real array )
variable b maxdim 4* 4- vallot ( np el. real vector )
variable c maxdim dup * 4* 4- vallot ( np*np real array )
variable d maxdim 4* 4- vallot ( np el. real vector )

: setup.vars 
 maxdim n1 ! 1 m1 ! ;

: read.str ( -- addr )
 pad 1+ 80 expect span @ pad c! pad ;

: num.inp.err
 .” numeric input error, reenter - “
;
: num.lim.err
 .” number outside limits, reenter - “
;
: read.int 
 begin read.str cr number? not while drop 
 num.inp.err
 repeat
;
: read.real
 begin read.str cr fnumber? not while fdrop 
 num.inp.err
 repeat
;
: read.int.limit { lo hi -- }
 begin
 read.int dup lo > over hi < and
 not while drop
 num.lim.err
 repeat
;
: read.real.limit ( flo fhi -- )
 begin
 fover fover
 read.real
 fswap fover f> fswap fover f< and
 not while fdrop
 num.lim.err
 repeat
 fswap fdrop fswap fdrop
;
: dumpAB { dim | -- }
 dim 0 do
 cr dim 0 do  
 i 5 * j + 4* a + @ s>f f.
 loop
 i 4* b + @ s>f f. 
 loop
;
 
: dumpC { dim | -- }
 dim 0 do
 cr dim 0 do  
 i 5 * j + 4* c + @ s>f f.
 loop
 loop
;

: gausstest { | dim -- } 
 cr
 setup.vars
 .” Enter problem dimension (min=1,max=10) : “ 
 0 n1 @ read.int.limit -> dim
 dim 0 do
 cr .” Enter row # “ i . .”  - “
 dim 0 do read.real f>s 
 i 5 * j + 4* a + ! \ store in array a
 loop
 read.real f>s i 4* b + ! \ store right-hand side
 loop
 a c 400 cmove \ copy a to c

 cr .” Calling GAUSSJ...”
 dim n ! 1 m !
 a n n1 b m m1 ierr gaussj
 cr .” After GAUSSJ. Components of A,B:”
 dim dumpAB
 cr .” Checking solution. Old A:” dim dumpC

 c b d n n1 n n1 m m1 matmul
 cr .” Old B: “
 dim 0 do
 i 4* d + @ s>f f.
 loop
 cr     
;

NEW.WINDOW lineq
“ Linear Equations” lineq TITLE
50 50 300 450 lineq BOUNDS
Document Visible NoCloseBox GrowBox lineq ITEMS

600 5000 terminal gauss

: go.gauss activate fp 7 fixed gausstest
 begin ?terminal until
 bye
;

: start
 lineq add
 lineq gauss build
 lineq dup call selectwindow call setport
 gauss go.gauss
; 
Listing 2: Fortran subroutines to be called from Mach2

!!S x2r 
 subroutine x2r(r,x)
 extended x
 real*4 r
 
 r = snglq(x)
 
 return
 end

!!S r2x 
 subroutine r2x(x,r)
 extended x
 real*4 r
 
 x = qext(r)
 
 return
 end

!!S Distance
 subroutine distance (r,y,x)
 implicit none
 extended x(3),y(3),r,x1,x2,x3
 
 x1 = x(1)-y(1)
 x2 = x(2)-y(2)
 x3 = x(3)-y(3)
 
 r = sqrt(x1*x1 + x2*x2 + x3*x3)
 
 return
 end

!!M Inlines.f
!!S makearray
 subroutine makearray (arraysize, myarray)
 implicit none

 integer*4 arraysize
 include ‘::fincludes:memtypes.f’
 
 structure /array/
 integer*4 f(1)
 end structure
 
 structure /Parray/
 pointer /array/ P
 end structure
 
 structure /Harray/
 pointer /Parray/ H
 end structure

 record /Harray/ myarray

 integer i,j
c
csets up new array of length arraysize
cand initializes it.
creturns -1 in arraysize 
cwhen the handle couldn’t be created.
c
 j = newHandle(%val(arraysize*4))
 if (j.ne.0) then
 myarray.h = j
 
 do i=1,arraysize
 myarray.h^.p^.f(i) = i
 end do
 
 else
 arraysize = -1
 end if
 
 return
 end

!!S matmul
 subroutine matmul (lp,l,mp,m,np,n,c,b,a)
c
cgenerates the matrix product c = a*b.
ca is an input matrix of dimensions m*n, stored in 
can array of physical dimensions mp*np.
cb is an input matrix of dimensions n*l, stored in 
can array of physical dimensions np*lp.
cc is the product matrix of dimensions m*l, stored in 
can array of physical dimensions mp*lp.
c
cJ. Langowski 1989
c
 implicit none
 integer*4 np,n,mp,m,lp,l
 real*4 a(mp,np),b(np,lp),c(mp,lp)
 
 real*4 sum
 integer*4 i,j,k
 
 do i=1,l
 do j=1,m
 sum=0.
 do k=1,n
 sum = sum + a(j,k)*b(k,i)
 end do
 c(j,i) = sum
 end do
 end do
 
 return
 end

!!S gaussj
 subroutine gaussj (ierr,mp,m,b,np,n,a)
c
c  linear equation solution by Gauss-Jordan elimination.
cA is an input matrix of N*N elements, stored in an array
cof physical dimensions NP*NP. B is an input matrix of 
cN*M containing the M right hand side vectors, stored 
cin an array of physical dimensions NP*MP. On output, A
cis replaced by its matrix inverse, and B is replaced by
cthe corresponding set of solution vectors.
c
cfrom: Press/Flannery/Teukolsky/Vetterling, 
cNumerical Recipes,  Cambridge University Press, 
cCambridge, UK 1986.
c
cJL \ added IERR for return of error status:
cIERR=0 no error
cIERR=-1singular matrix
c parameters are in inverse order wrt original 
cdefinition so that Mach2 can push them on the stack 
cin the original order.
c
 integer nmax
 parameter (nmax=50)
 
 integer*4 n,np,m,mp
 real*4 a(np,np),b(np,mp)
 
 integer*4 ipiv(nmax),indxr(nmax),indxc(nmax)
 integer*4 i,j,k,l,ll,irow,icol
 real*4 big,dum,pivinv
 
 do i=1,n
 ipiv(i) = 0
 end do
 do i=1,n
 big=0.
 do j=1,n
 if (ipiv(j) .ne. 1) then
 do k=1,n
 if (ipiv(k).eq.0) then
 if(abs(a(j,k)) .ge. big) then
 big = abs(a(j,k))
 irow=j
 icol=k
 end if
 else if (ipiv(k).gt.1) then
 ierr=-1
 return
 end if
 end do
 end if
 end do
 ipiv(icol)=ipiv(icol)+1
 
 if(irow.ne.icol) then
 do l=1,n
 dum=a(irow,l)
 a(irow,l)=a(icol,l)
 a(icol,l) = dum
 end do
 do l=1,m
 dum=b(irow,l)
 b(irow,l)=b(icol,l)
 b(icol,l)=dum
 end do
 end if
 
 indxr(i) = irow
 indxc(i) = icol
 if (a(icol,icol).eq.0.) then
 ierr=-1
 return
 end if
 pivinv=1./a(icol,icol)
 a(icol,icol)=1.
 
 do l=1,n
 a(icol,l)=a(icol,l)*pivinv
 end do
 do l=1,m
 b(icol,l)=b(icol,l)*pivinv
 end do
 do ll=1,n
 if (ll.ne.icol) then
 dum=a(ll,icol)
 a(ll,icol)=0.
 do l=1,n
 a(ll,l)=a(ll,l)-a(icol,l)*dum
 end do
 do l=1,m
 b(ll,l)=b(ll,l)-b(icol,l)*dum
 end do
 end if
 end do
 end do
 
 do l=n,1,-1
 if(indxr(l).ne.indxc(l)) then
 do k=1,n
 dum=a(k,indxr(l))
 a(k,indxr(l))=a(k,indxc(l))
 a(k,indxc(l))=dum
 end do
 end if
 end do
 
 ierr=0
 return
 end
 
 program gausstest
c
cmain program to test GAUSSJ and MATMUL
csubroutines
c
 implicit none
 integer*4 i,ierr,j,n,np
 real*4 a(10,10), b(10), c(10,10), d(10), sum
 
 np = 10
1write (6,*) ‘Enter problem dimension (max=10):’
 read (6,*) n
 if (n.ge.np .or. n.eq.0) goto 1
 do i=1,n
 write (6,*) ‘Enter row #’,i,’:’
 read (6,*) (a(i,j),j=1,n),b(i)
 do j=1,n
 c(i,j) = a(i,j)
 end do
 end do
 write (6,*) ‘Calling GAUSSJ...’
 call gaussj(ierr,1,1,b,np,n,a)
 write (6,*) ‘After GAUSSJ. Components of A, B:’
 do i=1,n
 write (6,*) (a(i,j),j=1,n),b(i)
 end do
 write (6,*) ‘Checking solution: original b(i):’
 do i=1,n
 sum = 0.
 do j=1,n
 sum = sum + c(i,j)*b(j)
 end do
 write (6,*) sum
 end do 
 call matmul (1,1,np,n,np,n,d,b,c)
 write (6,*) (d(i),i=1,n)
 goto 1
 end
Listing 3: MPW script to generate ‘machsub’ file and Fortran test application

fortran myarray.f
fortran distance.f
fortran x2r.f
fortran r2x.f
fortran matmul.f
fortran gaussj.f
fortran gausstest.f

link -b -w myarray.f.o -m MAKEARRAY 
 -t FTNp 
 “{FLibraries}FORTRANLib.o” 
 “{Libraries}Runtime.o” 
 “{Libraries}Interface.o” 
 -rt PROC=128 -o “machsub” -l >> machsub.map
link -b -w distance.f.o -m DISTANCE 
 -rt PROC=129 -o “machsub” -l >> machsub.map
link -b -w x2r.f.o -m X2R 
 -rt PROC=130 -o “machsub” -l >> machsub.map
link -b -w r2x.f.o -m R2X 
 -rt PROC=131 -o “machsub” -l >> machsub.map
link -b -w gaussj.f.o -m GAUSSJ 
 -sg gaussj=f_RunTime 
 “{FLibraries}FORTRANLib.o” 
 “{FLibraries}IntrinsicLib.o” 
 “{FLibraries}FSANELib.o” 
 “{Libraries}Runtime.o” 
 “{Libraries}Interface.o” 
 -rt PROC=132 -o “machsub” -l >> machsub.map
link -b -w matmul.f.o -m MATMUL 
 -sg matmul=f_RunTime 
 “{FLibraries}FORTRANLib.o” 
 “{Libraries}Runtime.o” 
 “{Libraries}Interface.o” 
 -rt PROC=133 -o “machsub” -l >> machsub.map
link -b -w gausstest.f.o gaussj.f.o matmul.f.o 
 “{FLibraries}FORTRANLib.o” 
 “{FLibraries}IntrinsicLib.o” 
 “{FLibraries}FSANELib.o” 
 “{Libraries}Runtime.o” 
 “{Libraries}Interface.o” 
 -o “gausstest” -l > gausstest.map
gausstest

 

Community Search:
MacTech Search:

Software Updates via MacUpdate

Latest Forum Discussions

See All

Whitethorn Games combines two completely...
If you have ever gone fishing then you know that it is a lesson in patience, sitting around waiting for a bite that may never come. Well, that's because you have been doing it wrong, since as Whitehorn Games now demonstrates in new release Skate... | Read more »
Call of Duty Warzone is a Waiting Simula...
It's always fun when a splashy multiplayer game comes to mobile because they are few and far between, so I was excited to see the notification about Call of Duty: Warzone Mobile (finally) launching last week and wanted to try it out. As someone who... | Read more »
Albion Online introduces some massive ne...
Sandbox Interactive has announced an upcoming update to its flagship MMORPG Albion Online, containing massive updates to its existing guild Vs guild systems. Someone clearly rewatched the Helms Deep battle in Lord of the Rings and spent the next... | Read more »
Chucklefish announces launch date of the...
Chucklefish, the indie London-based team we probably all know from developing Terraria or their stint publishing Stardew Valley, has revealed the mobile release date for roguelike deck-builder Wildfrost. Developed by Gaziter and Deadpan Games, the... | Read more »
Netmarble opens pre-registration for act...
It has been close to three years since Netmarble announced they would be adapting the smash series Solo Leveling into a video game, and at last, they have announced the opening of pre-orders for Solo Leveling: Arise. [Read more] | Read more »
PUBG Mobile celebrates sixth anniversary...
For the past six years, PUBG Mobile has been one of the most popular shooters you can play in the palm of your hand, and Krafton is celebrating this milestone and many years of ups by teaming up with hit music man JVKE to create a special song for... | Read more »
ASTRA: Knights of Veda refuse to pump th...
In perhaps the most recent example of being incredibly eager, ASTRA: Knights of Veda has dropped its second collaboration with South Korean boyband Seventeen, named so as it consists of exactly thirteen members and a video collaboration with Lee... | Read more »
Collect all your cats and caterpillars a...
If you are growing tired of trying to build a town with your phone by using it as a tiny, ineffectual shover then fear no longer, as Independent Arts Software has announced the upcoming release of Construction Simulator 4, from the critically... | Read more »
Backbone complete its lineup of 2nd Gene...
With all the ports of big AAA games that have been coming to mobile, it is becoming more convenient than ever to own a good controller, and to help with this Backbone has announced the completion of their 2nd generation product lineup with their... | Read more »
Zenless Zone Zero opens entries for its...
miHoYo, aka HoYoverse, has become such a big name in mobile gaming that it's hard to believe that arguably their flagship title, Genshin Impact, is only three and a half years old. Now, they continue the road to the next title in their world, with... | Read more »

Price Scanner via MacPrices.net

B&H has Apple’s 13-inch M2 MacBook Airs o...
B&H Photo has 13″ MacBook Airs with M2 CPUs and 256GB of storage in stock and on sale for up to $150 off Apple’s new MSRP, starting at only $849. Free 1-2 day delivery is available to most US... Read more
M2 Mac minis on sale for $100-$200 off MSRP,...
B&H Photo has Apple’s M2-powered Mac minis back in stock and on sale today for $100-$200 off MSRP. Free 1-2 day shipping is available for most US addresses: – Mac mini M2/256GB SSD: $499, save $... Read more
Mac Studios with M2 Max and M2 Ultra CPUs on...
B&H Photo has standard-configuration Mac Studios with Apple’s M2 Max & Ultra CPUs in stock today and on Easter sale for $200 off MSRP. Their prices are the lowest available for these models... Read more
Deal Alert! B&H Photo has Apple’s 14-inch...
B&H Photo has new Gray and Black 14″ M3, M3 Pro, and M3 Max MacBook Pros on sale for $200-$300 off MSRP, starting at only $1399. B&H offers free 1-2 day delivery to most US addresses: – 14″ 8... Read more
Department Of Justice Sets Sights On Apple In...
NEWS – The ball has finally dropped on the big Apple. The ball (metaphorically speaking) — an antitrust lawsuit filed in the U.S. on March 21 by the Department of Justice (DOJ) — came down following... Read more
New 13-inch M3 MacBook Air on sale for $999,...
Amazon has Apple’s new 13″ M3 MacBook Air on sale for $100 off MSRP for the first time, now just $999 shipped. Shipping is free: – 13″ MacBook Air (8GB RAM/256GB SSD/Space Gray): $999 $100 off MSRP... Read more
Amazon has Apple’s 9th-generation WiFi iPads...
Amazon has Apple’s 9th generation 10.2″ WiFi iPads on sale for $80-$100 off MSRP, starting only $249. Their prices are the lowest available for new iPads anywhere: – 10″ 64GB WiFi iPad (Space Gray or... Read more
Discounted 14-inch M3 MacBook Pros with 16GB...
Apple retailer Expercom has 14″ MacBook Pros with M3 CPUs and 16GB of standard memory discounted by up to $120 off Apple’s MSRP: – 14″ M3 MacBook Pro (16GB RAM/256GB SSD): $1691.06 $108 off MSRP – 14... Read more
Clearance 15-inch M2 MacBook Airs on sale for...
B&H Photo has Apple’s 15″ MacBook Airs with M2 CPUs (8GB RAM/256GB SSD) in stock today and on clearance sale for $999 in all four colors. Free 1-2 delivery is available to most US addresses.... Read more
Clearance 13-inch M1 MacBook Airs drop to onl...
B&H has Apple’s base 13″ M1 MacBook Air (Space Gray, Silver, & Gold) in stock and on clearance sale today for $300 off MSRP, only $699. Free 1-2 day shipping is available to most addresses in... Read more

Jobs Board

Medical Assistant - Surgical Oncology- *Apple...
Medical Assistant - Surgical Oncology- Apple Hill Location: WellSpan Medical Group, York, PA Schedule: Full Time Sign-On Bonus Eligible Remote/Hybrid Regular Apply Read more
Omnichannel Associate - *Apple* Blossom Mal...
Omnichannel Associate - Apple Blossom Mall Location:Winchester, VA, United States (https://jobs.jcp.com/jobs/location/191170/winchester-va-united-states) - Apple Read more
Cashier - *Apple* Blossom Mall - JCPenney (...
Cashier - Apple Blossom Mall Location:Winchester, VA, United States (https://jobs.jcp.com/jobs/location/191170/winchester-va-united-states) - Apple Blossom Mall Read more
Operations Associate - *Apple* Blossom Mall...
Operations Associate - Apple Blossom Mall Location:Winchester, VA, United States (https://jobs.jcp.com/jobs/location/191170/winchester-va-united-states) - Apple Read more
Business Analyst | *Apple* Pay - Banco Popu...
Business Analyst | Apple PayApply now " Apply now + Apply Now + Start applying with LinkedIn Start + Please wait Date:Mar 19, 2024 Location: San Juan-Cupey, PR Read more
All contents are Copyright 1984-2011 by Xplain Corporation. All rights reserved. Theme designed by Icreon.