-
Notifications
You must be signed in to change notification settings - Fork 21
Example usage to build other tools
The following simple Haskell example shows how to import the general parser module, fix the language version to Fortran 90, parse some code into the AST, and then print it to standard output:
module Tmp where
import qualified Language.Fortran.Parser as F.Parser
import qualified Language.Fortran.Version as F
import qualified Data.ByteString.Char8 as B
main :: IO ()
main = do
v <- askFortranVersion
let parse = F.Parser.byVer v
case parse "<no file>" program of
Left err -> putStrLn $ "parse error: " <> show err
Right ast -> print ast
askFortranVersion :: IO F.FortranVersion
askFortranVersion = return F.Fortran90
program :: B.ByteString
program = B.pack $ unlines $
[ "function area_of_circle(r) result(area)"
, " real, parameter :: pi = 3.14"
, " real, intent(in) :: r"
, " real :: area"
, " area = r * r * pi"
, "end function"
, ""
, "program main"
, " print *, area_of_circle(1.0)"
, "end program"
]
A simple way of testing this example is to install the fortran-src
package via cabal (i.e., cabal install fortran-src
) to make it
available within your environment for GHC.
Let's say we wish to write a new Fortran code analysis using fortran-src. Fortran 90 introduced allocatable arrays, which enable declaring and using dynamic arrays in a straightforward manner. Allocatable arrays are declared only with the scalar type and rank, omitting the upper bound:
integer, dimension(:), allocatable :: xs
A newly-declared allocatable begins unallocated. Reading from an unallocated
array is an erroneous operation. You must first allocate
the array with
dimensions:
! allocate memory for an array of 5 integers
! (note that the array is not initialized)
allocate(xs(5))
When finished, you must manually deallocate
the array.
deallocate(xs)
Arrays must be deallocated before they go out of scope, or else risk leaking
memory. As an example use of fortran-src,
we show here a simple code pass that asserts this property. Since arrays
may be deallocated and re-allocated during their lifetime, we shall track the
allocatables currently in scope, and assert that all are unallocated at the end
of the program unit. Fortran being highly procedural means it lends itself to
monadic program composition, so we first design a monad that supports tracking
allocatables. (We use the effectful
effect library here, but the details are
insignificant). The full code listing is available online.
import qualified Language.Fortran.AST as F
-- ....
-- Declare an effectful interface for the static analysis
data Analysis :: Effect where
DeclareVar :: F.Name -> Analysis m ()
MakeVarAllocatable :: F.Name -> Analysis m ()
AllocVar :: F.Name -> Analysis m ()
DeallocVar :: F.Name -> Analysis m ()
AskVar :: F.Name -> Analysis m (Maybe VarState)
-- extra: enable emitting other semi-relevant analysis info
EmitErr :: String -> Analysis m a
EmitWarn :: String -> String -> Analysis m ()
-- Representation of variable information for the analysis
data VarState
-- | Declared.
= VarIsFresh
-- | Allocatable. Counts number of times allocated.
| VarIsAllocatable AllocState Int
deriving stock Show
data AllocState
= Allocd
| Unallocd
deriving stock Show
Now we can design a mini program in this monad by pattern matching on the Fortran AST data types from fortran-src:
-- Analyse statements
analyseStmt :: Analysis :> es => F.Statement a -> Eff es ()
analyseStmt = \case
-- Emit declarations
F.StDeclaration _ _ _ attribs decls ->
traverse_ (declare attribs) (F.aStrip decls)
-- Emit allocatable names
F.StAllocatable _ _ decls ->
traverse_ makeAllocatable (F.aStrip decls)
-- Emit allocated variables
F.StAllocate _ _ _ es _ ->
traverse_ allocate (F.aStrip es)
-- Emit deallocated variables
F.StDeallocate _ _ es _ ->
traverse_ deallocate (F.aStrip es)
-- Check usage in any other statements
st -> analyseStmtAccess st
-- Handle a declaration
declare
:: Analysis :> es
=> Maybe (F.AList F.Attribute a) -> F.Declarator a -> Eff es ()
declare mAttribs d =
case F.declaratorVariable d of
F.ExpValue _ _ (F.ValVariable dv) -> do
declareVar dv
case mAttribs of
Nothing -> pure ()
Just attribs ->
if attribListIncludesAllocatable (F.aStrip attribs)
then makeVarAllocatable dv
else pure ()
_ -> emitWarn "bad declarator form" "ignoring"
-- Handle an allocation expression
allocate :: Analysis :> es => F.Expression a -> Eff es ()
allocate = \case
F.ExpSubscript _ _ (F.ExpValue _ _ (F.ValVariable v)) _dims ->
allocVar v
_ -> emitWarn "unsupported ALLOCATE form" "ignoring"
-- Handle a deallocation expression
deallocate :: Analysis :> es => F.Expression a -> Eff es ()
deallocate = \case
F.ExpValue _ _ (F.ValVariable v) ->
deallocVar v
_ -> emitWarn "unsupported DEALLOCATE form" "ignoring"
We wish to evaluate this mini program to receive a report of the allocatable
variables and whether they were properly deallocated. A state monad holding a
map of variable names to VarState
entries can implement this, and we bolt this on
top of IO
for easy emission of warnings and errors.
The runAnalysis
function then handles the effect interface, using
the stateful map to store information about our variables, i.e., whether
they are allocatable, allocated, deallocated, or neither:
-- 'F.Name' is the type synonym for variable names
type Ctx = Map F.Name VarState
runAnalysis
:: (IOE :> es, State Ctx :> es)
=> Eff (Analysis : es) a
-> Eff es a
-- e.g. @'AskVar' v@ gets mapped to @'Map.lookup' v ctx@
For the sake of brevity, we include just the code for handling the deallocation operation. To handle deallocations, we look up the deallocated variable in the map and report on various behaviours that would be program errors in the Fortran code: (1) the deallocated variable does not exist; (2) the deallocated variable is not allocatable; (3) the deallocated variable is allocatable but has not been allocated.
Lastly (4) is a non-buggy situation where the deallocated variable is allocatable and is allocated, but is not marked as unallocated.
DeallocVar v -> do
st <- State.get
case Map.lookup v st of
-- (1) Variable was never declared
Nothing -> err "tried to deallocate undeclared var"
-- ... variable is declared
Just vst ->
case vst of
-- (2) Variable is not allocatable
VarIsFresh -> err "tried to deallocate unallocatable var"
-- ... variable is allocatable
VarIsAllocatable vstAllocState vstAllocCount ->
-- Check its state
case vstAllocState of
-- (3) Trying to deallocate unallocated variable
Unallocd -> err "tried to deallocate unallocated var"
-- (4) Deallocating allocated variable
Allocd -> do
let vst' = VarIsAllocatable Unallocd vstAllocCount
State.put $ Map.insert v vst' st
Note, this analysis does not handle control flow operators. Further work may involve tracking allocatable status specially in data flow analyses.