{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE UndecidableInstances #-}
{-# OPTIONS_GHC -Wno-orphans #-}
module Language.Fortran.PrettyPrint where
import Data.Maybe (isJust, isNothing, listToMaybe)
import Data.List (foldl')
import Prelude hiding (EQ,LT,GT,pred,exp,(<>))
import Language.Fortran.AST
import Language.Fortran.ParserMonad
import Language.Fortran.Util.FirstParameter
import Text.PrettyPrint
tooOld :: FortranVersion -> String -> FortranVersion -> a
tooOld :: FortranVersion -> String -> FortranVersion -> a
tooOld FortranVersion
currentVersion String
featureName FortranVersion
featureVersion = String -> a
forall a. HasCallStack => String -> a
error (String -> a) -> String -> a
forall a b. (a -> b) -> a -> b
$
String
featureName String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" was introduced in " String -> String -> String
forall a. [a] -> [a] -> [a]
++ FortranVersion -> String
forall a. Show a => a -> String
show FortranVersion
featureVersion String -> String -> String
forall a. [a] -> [a] -> [a]
++
String
". You called pretty print with " String -> String -> String
forall a. [a] -> [a] -> [a]
++ FortranVersion -> String
forall a. Show a => a -> String
show FortranVersion
currentVersion String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"."
(<?>) :: Doc -> Doc -> Doc
Doc
doc1 <?> :: Doc -> Doc -> Doc
<?> Doc
doc2 = if Doc
doc1 Doc -> Doc -> Bool
forall a. Eq a => a -> a -> Bool
== Doc
empty Bool -> Bool -> Bool
|| Doc
doc2 Doc -> Doc -> Bool
forall a. Eq a => a -> a -> Bool
== Doc
empty then Doc
empty else Doc
doc1 Doc -> Doc -> Doc
<> Doc
doc2
infixl 7 <?>
(<?+>) :: Doc -> Doc -> Doc
Doc
doc1 <?+> :: Doc -> Doc -> Doc
<?+> Doc
doc2 = if Doc
doc1 Doc -> Doc -> Bool
forall a. Eq a => a -> a -> Bool
== Doc
empty Bool -> Bool -> Bool
|| Doc
doc2 Doc -> Doc -> Bool
forall a. Eq a => a -> a -> Bool
== Doc
empty then Doc
empty else Doc
doc1 Doc -> Doc -> Doc
<+> Doc
doc2
infixl 7 <?+>
newline :: Doc
newline :: Doc
newline = Char -> Doc
char Char
'\n'
type Indentation = Maybe Int
incIndentation :: Indentation -> Indentation
incIndentation :: Indentation -> Indentation
incIndentation Indentation
indentation = (Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
2) (Int -> Int) -> Indentation -> Indentation
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Indentation
indentation
indent :: Indentation -> Doc -> Doc
indent :: Indentation -> Doc -> Doc
indent Indentation
Nothing Doc
d = Doc
d
indent (Just Int
i) Doc
d = String -> Doc
text (Int -> Char -> String
forall a. Int -> a -> [a]
replicate Int
i Char
' ') Doc -> Doc -> Doc
<> Doc
d
overlay :: Doc -> Doc -> Doc
overlay :: Doc -> Doc -> Doc
overlay Doc
top Doc
bottom = String -> Doc
text (String -> Doc) -> String -> Doc
forall a b. (a -> b) -> a -> b
$ String
top' String -> String -> String
forall a. [a] -> [a] -> [a]
++ Int -> String -> String
forall a. Int -> [a] -> [a]
drop (String -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length String
top') (Doc -> String
render Doc
bottom)
where top' :: String
top' = Doc -> String
render Doc
top
fixedForm :: Indentation
fixedForm :: Indentation
fixedForm = Int -> Indentation
forall a. a -> Maybe a
Just Int
6
pprintAndRender :: IndentablePretty t => FortranVersion -> t -> Indentation -> String
pprintAndRender :: FortranVersion -> t -> Indentation -> String
pprintAndRender FortranVersion
v t
t Indentation
i = Doc -> String
render (Doc -> String) -> Doc -> String
forall a b. (a -> b) -> a -> b
$ FortranVersion -> t -> Indentation -> Doc
forall t.
IndentablePretty t =>
FortranVersion -> t -> Indentation -> Doc
pprint FortranVersion
v t
t Indentation
i
class IndentablePretty t where
pprint :: FortranVersion -> t -> Indentation -> Doc
instance {-# OVERLAPPABLE #-} Pretty a => IndentablePretty a where
pprint :: FortranVersion -> a -> Indentation -> Doc
pprint FortranVersion
v a
t Indentation
_ = FortranVersion -> a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v a
t
instance IndentablePretty a => IndentablePretty (Maybe a) where
pprint :: FortranVersion -> Maybe a -> Indentation -> Doc
pprint FortranVersion
v (Just a
t) Indentation
i = FortranVersion -> a -> Indentation -> Doc
forall t.
IndentablePretty t =>
FortranVersion -> t -> Indentation -> Doc
pprint FortranVersion
v a
t Indentation
i
pprint FortranVersion
_ Maybe a
Nothing Indentation
_ = Doc
empty
instance IndentablePretty (ProgramFile a) where
pprint :: FortranVersion -> ProgramFile a -> Indentation -> Doc
pprint FortranVersion
v (ProgramFile MetaInfo
_ [ProgramUnit a]
programUnits) Indentation
i =
(Doc -> ProgramUnit a -> Doc) -> Doc -> [ProgramUnit a] -> Doc
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' (\Doc
b ProgramUnit a
a -> Doc
b Doc -> Doc -> Doc
<> ProgramUnit a -> Doc
forall t. IndentablePretty t => t -> Doc
pprintUnit ProgramUnit a
a) Doc
empty [ProgramUnit a]
programUnits
where
pprintUnit :: t -> Doc
pprintUnit t
pu = FortranVersion -> t -> Indentation -> Doc
forall t.
IndentablePretty t =>
FortranVersion -> t -> Indentation -> Doc
pprint FortranVersion
v t
pu Indentation
i
instance IndentablePretty [ProgramUnit a] where
pprint :: FortranVersion -> [ProgramUnit a] -> Indentation -> Doc
pprint FortranVersion
v [ProgramUnit a]
pus Indentation
i = (Doc -> ProgramUnit a -> Doc) -> Doc -> [ProgramUnit a] -> Doc
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' (\Doc
b ProgramUnit a
a -> Doc
b Doc -> Doc -> Doc
<?> Doc
newline Doc -> Doc -> Doc
<> FortranVersion -> ProgramUnit a -> Indentation -> Doc
forall t.
IndentablePretty t =>
FortranVersion -> t -> Indentation -> Doc
pprint FortranVersion
v ProgramUnit a
a Indentation
i) Doc
empty [ProgramUnit a]
pus
instance IndentablePretty (ProgramUnit a) where
pprint :: FortranVersion -> ProgramUnit a -> Indentation -> Doc
pprint FortranVersion
v (PUMain a
_ SrcSpan
_ Maybe String
mName [Block a]
body Maybe [ProgramUnit a]
mSubs) Indentation
i
| FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
< FortranVersion
Fortran77 =
if Maybe String -> Bool
forall a. Maybe a -> Bool
isJust Maybe String
mName
then FortranVersion -> String -> FortranVersion -> Doc
forall a. FortranVersion -> String -> FortranVersion -> a
tooOld FortranVersion
v String
"Named main program unit" FortranVersion
Fortran77
else
if Maybe [ProgramUnit a] -> Bool
forall a. Maybe a -> Bool
isJust Maybe [ProgramUnit a]
mSubs
then FortranVersion -> String -> FortranVersion -> Doc
forall a. FortranVersion -> String -> FortranVersion -> a
tooOld FortranVersion
v String
"Subprogram unit" FortranVersion
Fortran90
else FortranVersion -> [Block a] -> Indentation -> Doc
forall t.
IndentablePretty t =>
FortranVersion -> t -> Indentation -> Doc
pprint FortranVersion
v [Block a]
body Indentation
fixedForm Doc -> Doc -> Doc
<>
Indentation -> Doc -> Doc
indent Indentation
fixedForm (Doc
"end" Doc -> Doc -> Doc
<> Doc
newline)
| FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
< FortranVersion
Fortran90 =
Indentation -> Doc -> Doc
indent Indentation
fixedForm (Doc
"program" Doc -> Doc -> Doc
<?+> FortranVersion -> Maybe String -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Maybe String
mName Doc -> Doc -> Doc
<?> Doc
newline) Doc -> Doc -> Doc
<>
if Maybe [ProgramUnit a] -> Bool
forall a. Maybe a -> Bool
isJust Maybe [ProgramUnit a]
mSubs
then FortranVersion -> String -> FortranVersion -> Doc
forall a. FortranVersion -> String -> FortranVersion -> a
tooOld FortranVersion
v String
"Subprogram unit" FortranVersion
Fortran90
else FortranVersion -> [Block a] -> Indentation -> Doc
forall t.
IndentablePretty t =>
FortranVersion -> t -> Indentation -> Doc
pprint FortranVersion
v [Block a]
body Indentation
fixedForm Doc -> Doc -> Doc
<>
Indentation -> Doc -> Doc
indent Indentation
fixedForm (Doc
"end" Doc -> Doc -> Doc
<> Doc
newline)
| Bool
otherwise =
Indentation -> Doc -> Doc
indent Indentation
i (Doc
"program" Doc -> Doc -> Doc
<?+> FortranVersion -> Maybe String -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Maybe String
mName Doc -> Doc -> Doc
<?> Doc
newline) Doc -> Doc -> Doc
<>
FortranVersion -> [Block a] -> Indentation -> Doc
forall t.
IndentablePretty t =>
FortranVersion -> t -> Indentation -> Doc
pprint FortranVersion
v [Block a]
body Indentation
nextI Doc -> Doc -> Doc
<>
Doc
newline Doc -> Doc -> Doc
<?>
Indentation -> Doc -> Doc
indent Indentation
nextI (Doc
"contains" Doc -> Doc -> Doc
<> Doc
newline) Doc -> Doc -> Doc
<?>
Doc
newline Doc -> Doc -> Doc
<?>
FortranVersion -> Maybe [ProgramUnit a] -> Indentation -> Doc
forall t.
IndentablePretty t =>
FortranVersion -> t -> Indentation -> Doc
pprint FortranVersion
v Maybe [ProgramUnit a]
mSubs Indentation
nextI Doc -> Doc -> Doc
<>
Indentation -> Doc -> Doc
indent Indentation
i (Doc
"end" Doc -> Doc -> Doc
<> Doc
" program" Doc -> Doc -> Doc
<?+> FortranVersion -> Maybe String -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Maybe String
mName Doc -> Doc -> Doc
<> Doc
newline)
where
nextI :: Indentation
nextI = Indentation -> Indentation
incIndentation Indentation
i
pprint FortranVersion
v (PUModule a
_ SrcSpan
_ String
name [Block a]
body Maybe [ProgramUnit a]
mSubs) Indentation
i
| FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= FortranVersion
Fortran90 =
Indentation -> Doc -> Doc
indent Indentation
i (Doc
"module" Doc -> Doc -> Doc
<+> String -> Doc
text String
name Doc -> Doc -> Doc
<> Doc
newline) Doc -> Doc -> Doc
<>
FortranVersion -> [Block a] -> Indentation -> Doc
forall t.
IndentablePretty t =>
FortranVersion -> t -> Indentation -> Doc
pprint FortranVersion
v [Block a]
body Indentation
nextI Doc -> Doc -> Doc
<>
Doc
newline Doc -> Doc -> Doc
<?>
Indentation -> Doc -> Doc
indent Indentation
nextI (Doc
"contains" Doc -> Doc -> Doc
<?> Doc
newline) Doc -> Doc -> Doc
<?>
Doc
newline Doc -> Doc -> Doc
<?>
FortranVersion -> Maybe [ProgramUnit a] -> Indentation -> Doc
forall t.
IndentablePretty t =>
FortranVersion -> t -> Indentation -> Doc
pprint FortranVersion
v Maybe [ProgramUnit a]
mSubs Indentation
nextI Doc -> Doc -> Doc
<>
Indentation -> Doc -> Doc
indent Indentation
i (Doc
"end module" Doc -> Doc -> Doc
<+> String -> Doc
text String
name Doc -> Doc -> Doc
<> Doc
newline)
| Bool
otherwise = FortranVersion -> String -> FortranVersion -> Doc
forall a. FortranVersion -> String -> FortranVersion -> a
tooOld FortranVersion
v String
"Module system" FortranVersion
Fortran90
where
nextI :: Indentation
nextI = Indentation -> Indentation
incIndentation Indentation
i
pprint FortranVersion
v (PUSubroutine a
_ SrcSpan
_ (Prefixes a
mpfxs, Suffixes a
msfxs) String
name Maybe (AList Expression a)
mArgs [Block a]
body Maybe [ProgramUnit a]
mSubs) Indentation
i =
Indentation -> Doc -> Doc
indent Indentation
curI
(Doc
prefix Doc -> Doc -> Doc
<+> Doc
"subroutine" Doc -> Doc -> Doc
<+> String -> Doc
text String
name Doc -> Doc -> Doc
<>
Doc
lparen Doc -> Doc -> Doc
<?> FortranVersion -> Maybe (AList Expression a) -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Maybe (AList Expression a)
mArgs Doc -> Doc -> Doc
<?> Doc
rparen Doc -> Doc -> Doc
<+> Doc
suffix Doc -> Doc -> Doc
<> Doc
newline) Doc -> Doc -> Doc
<>
FortranVersion -> [Block a] -> Indentation -> Doc
forall t.
IndentablePretty t =>
FortranVersion -> t -> Indentation -> Doc
pprint FortranVersion
v [Block a]
body Indentation
nextI Doc -> Doc -> Doc
<>
Doc
newline Doc -> Doc -> Doc
<?>
Indentation -> Doc -> Doc
indent Indentation
nextI (Doc
"contains" Doc -> Doc -> Doc
<> Doc
newline) Doc -> Doc -> Doc
<?>
Doc
newline Doc -> Doc -> Doc
<?>
Doc
subs Doc -> Doc -> Doc
<>
FortranVersion -> Doc -> String -> Indentation -> Doc
forall a.
Pretty a =>
FortranVersion -> Doc -> a -> Indentation -> Doc
endGen FortranVersion
v Doc
"subroutine" String
name Indentation
curI
where
convPfx :: Prefix a -> p
convPfx (PfxElemental a
_ SrcSpan
_)
| FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= FortranVersion
Fortran95 = p
"elemental"
| Bool
otherwise = FortranVersion -> String -> FortranVersion -> p
forall a. FortranVersion -> String -> FortranVersion -> a
tooOld FortranVersion
v String
"Elemental function" FortranVersion
Fortran95
convPfx (PfxPure a
_ SrcSpan
_)
| FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= FortranVersion
Fortran95 = p
"pure"
| Bool
otherwise = FortranVersion -> String -> FortranVersion -> p
forall a. FortranVersion -> String -> FortranVersion -> a
tooOld FortranVersion
v String
"Pure function" FortranVersion
Fortran95
convPfx (PfxRecursive a
_ SrcSpan
_)
| FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= FortranVersion
Fortran90 = p
"recursive"
| Bool
otherwise = FortranVersion -> String -> FortranVersion -> p
forall a. FortranVersion -> String -> FortranVersion -> a
tooOld FortranVersion
v String
"Recursive function" FortranVersion
Fortran90
prefix :: Doc
prefix = [Doc] -> Doc
hsep ((Prefix a -> Doc) -> [Prefix a] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map Prefix a -> Doc
forall p a. IsString p => Prefix a -> p
convPfx [Prefix a]
pfxs)
suffix :: Doc
suffix = FortranVersion -> Maybe (Suffix a) -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v ([Suffix a] -> Maybe (Suffix a)
forall a. [a] -> Maybe a
listToMaybe [Suffix a]
sfxs)
subs :: Doc
subs
| Maybe [ProgramUnit a] -> Bool
forall a. Maybe a -> Bool
isJust Maybe [ProgramUnit a]
mSubs, FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= FortranVersion
Fortran90 = FortranVersion -> Maybe [ProgramUnit a] -> Indentation -> Doc
forall t.
IndentablePretty t =>
FortranVersion -> t -> Indentation -> Doc
pprint FortranVersion
v Maybe [ProgramUnit a]
mSubs Indentation
nextI
| Maybe [ProgramUnit a] -> Bool
forall a. Maybe a -> Bool
isNothing Maybe [ProgramUnit a]
mSubs = Doc
empty
| Bool
otherwise = FortranVersion -> String -> FortranVersion -> Doc
forall a. FortranVersion -> String -> FortranVersion -> a
tooOld FortranVersion
v String
"Function subprogram" FortranVersion
Fortran90
curI :: Indentation
curI = if FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= FortranVersion
Fortran90 then Indentation
i else Indentation
fixedForm
nextI :: Indentation
nextI = if FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= FortranVersion
Fortran90 then Indentation -> Indentation
incIndentation Indentation
i
else Indentation -> Indentation
incIndentation Indentation
fixedForm
pfxs :: [Prefix a]
pfxs = Prefixes a -> [Prefix a]
forall (t :: * -> *) a. Maybe (AList t a) -> [t a]
aStrip' Prefixes a
mpfxs
sfxs :: [Suffix a]
sfxs = Suffixes a -> [Suffix a]
forall (t :: * -> *) a. Maybe (AList t a) -> [t a]
aStrip' Suffixes a
msfxs
pprint FortranVersion
v (PUFunction a
_ SrcSpan
_ Maybe (TypeSpec a)
mRetType (Prefixes a
mpfxs, Suffixes a
msfxs) String
name Maybe (AList Expression a)
mArgs Maybe (Expression a)
mRes [Block a]
body Maybe [ProgramUnit a]
mSubs) Indentation
i =
Indentation -> Doc -> Doc
indent Indentation
curI
(Doc
prefix Doc -> Doc -> Doc
<+> Doc
"function" Doc -> Doc -> Doc
<+> String -> Doc
text String
name Doc -> Doc -> Doc
<>
Doc -> Doc
parens (FortranVersion -> Maybe (AList Expression a) -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Maybe (AList Expression a)
mArgs) Doc -> Doc -> Doc
<+> Doc
suffix Doc -> Doc -> Doc
<> Doc
newline) Doc -> Doc -> Doc
<>
FortranVersion -> [Block a] -> Indentation -> Doc
forall t.
IndentablePretty t =>
FortranVersion -> t -> Indentation -> Doc
pprint FortranVersion
v [Block a]
body Indentation
nextI Doc -> Doc -> Doc
<>
Doc
newline Doc -> Doc -> Doc
<?>
Indentation -> Doc -> Doc
indent Indentation
nextI (Doc
"contains" Doc -> Doc -> Doc
<> Doc
newline) Doc -> Doc -> Doc
<?>
Doc
newline Doc -> Doc -> Doc
<?>
Doc
subs Doc -> Doc -> Doc
<>
FortranVersion -> Doc -> String -> Indentation -> Doc
forall a.
Pretty a =>
FortranVersion -> Doc -> a -> Indentation -> Doc
endGen FortranVersion
v Doc
"function" String
name Indentation
curI
where
convPfx :: Prefix a -> p
convPfx (PfxElemental a
_ SrcSpan
_)
| FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= FortranVersion
Fortran95 = p
"elemental"
| Bool
otherwise = FortranVersion -> String -> FortranVersion -> p
forall a. FortranVersion -> String -> FortranVersion -> a
tooOld FortranVersion
v String
"Elemental function" FortranVersion
Fortran95
convPfx (PfxPure a
_ SrcSpan
_)
| FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= FortranVersion
Fortran95 = p
"pure"
| Bool
otherwise = FortranVersion -> String -> FortranVersion -> p
forall a. FortranVersion -> String -> FortranVersion -> a
tooOld FortranVersion
v String
"Pure function" FortranVersion
Fortran95
convPfx (PfxRecursive a
_ SrcSpan
_)
| FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= FortranVersion
Fortran90 = p
"recursive"
| Bool
otherwise = FortranVersion -> String -> FortranVersion -> p
forall a. FortranVersion -> String -> FortranVersion -> a
tooOld FortranVersion
v String
"Recursive function" FortranVersion
Fortran90
prefix :: Doc
prefix = [Doc] -> Doc
hsep (FortranVersion -> Maybe (TypeSpec a) -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Maybe (TypeSpec a)
mRetTypeDoc -> [Doc] -> [Doc]
forall a. a -> [a] -> [a]
:(Prefix a -> Doc) -> [Prefix a] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map Prefix a -> Doc
forall p a. IsString p => Prefix a -> p
convPfx [Prefix a]
pfxs)
result :: Doc
result
| Maybe (Expression a) -> Bool
forall a. Maybe a -> Bool
isJust Maybe (Expression a)
mRes, FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= FortranVersion
Fortran90 = Doc
"result" Doc -> Doc -> Doc
<?> Doc
lparen Doc -> Doc -> Doc
<?> FortranVersion -> Maybe (Expression a) -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Maybe (Expression a)
mRes Doc -> Doc -> Doc
<?> Doc
rparen
| Maybe (Expression a) -> Bool
forall a. Maybe a -> Bool
isNothing Maybe (Expression a)
mRes = Doc
empty
| Bool
otherwise = FortranVersion -> String -> FortranVersion -> Doc
forall a. FortranVersion -> String -> FortranVersion -> a
tooOld FortranVersion
v String
"Function result" FortranVersion
Fortran90
suffix :: Doc
suffix = Doc
result Doc -> Doc -> Doc
<+> FortranVersion -> Maybe (Suffix a) -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v ([Suffix a] -> Maybe (Suffix a)
forall a. [a] -> Maybe a
listToMaybe [Suffix a]
sfxs)
subs :: Doc
subs
| Maybe [ProgramUnit a] -> Bool
forall a. Maybe a -> Bool
isJust Maybe [ProgramUnit a]
mSubs, FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= FortranVersion
Fortran90 = FortranVersion -> Maybe [ProgramUnit a] -> Indentation -> Doc
forall t.
IndentablePretty t =>
FortranVersion -> t -> Indentation -> Doc
pprint FortranVersion
v Maybe [ProgramUnit a]
mSubs Indentation
nextI
| Maybe [ProgramUnit a] -> Bool
forall a. Maybe a -> Bool
isNothing Maybe [ProgramUnit a]
mSubs = Doc
empty
| Bool
otherwise = FortranVersion -> String -> FortranVersion -> Doc
forall a. FortranVersion -> String -> FortranVersion -> a
tooOld FortranVersion
v String
"Function subprogram" FortranVersion
Fortran90
curI :: Indentation
curI = if FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= FortranVersion
Fortran90 then Indentation
i else Indentation
fixedForm
nextI :: Indentation
nextI = if FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= FortranVersion
Fortran90 then Indentation -> Indentation
incIndentation Indentation
i
else Indentation -> Indentation
incIndentation Indentation
fixedForm
pfxs :: [Prefix a]
pfxs = Prefixes a -> [Prefix a]
forall (t :: * -> *) a. Maybe (AList t a) -> [t a]
aStrip' Prefixes a
mpfxs
sfxs :: [Suffix a]
sfxs = Suffixes a -> [Suffix a]
forall (t :: * -> *) a. Maybe (AList t a) -> [t a]
aStrip' Suffixes a
msfxs
pprint FortranVersion
v (PUBlockData a
_ SrcSpan
_ Maybe String
mName [Block a]
body) Indentation
i
| FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
< FortranVersion
Fortran77, Maybe String -> Bool
forall a. Maybe a -> Bool
isJust Maybe String
mName = FortranVersion -> String -> FortranVersion -> Doc
forall a. FortranVersion -> String -> FortranVersion -> a
tooOld FortranVersion
v String
"Named block data" FortranVersion
Fortran77
| Bool
otherwise =
Indentation -> Doc -> Doc
indent Indentation
curI (Doc
"block data" Doc -> Doc -> Doc
<+> FortranVersion -> Maybe String -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Maybe String
mName Doc -> Doc -> Doc
<> Doc
newline) Doc -> Doc -> Doc
<>
FortranVersion -> [Block a] -> Indentation -> Doc
forall t.
IndentablePretty t =>
FortranVersion -> t -> Indentation -> Doc
pprint FortranVersion
v [Block a]
body Indentation
nextI Doc -> Doc -> Doc
<>
FortranVersion -> Doc -> Maybe String -> Indentation -> Doc
forall a.
Pretty a =>
FortranVersion -> Doc -> a -> Indentation -> Doc
endGen FortranVersion
v Doc
"block data" Maybe String
mName Indentation
curI
where
curI :: Indentation
curI = if FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= FortranVersion
Fortran90 then Indentation
i else Indentation
fixedForm
nextI :: Indentation
nextI = if FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= FortranVersion
Fortran90
then Indentation -> Indentation
incIndentation Indentation
i
else Indentation -> Indentation
incIndentation Indentation
fixedForm
pprint FortranVersion
v (PUComment a
_ SrcSpan
_ (Comment String
comment)) Indentation
i
| FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= FortranVersion
Fortran90 = Indentation -> Doc -> Doc
indent Indentation
i (Char -> Doc
char Char
'!' Doc -> Doc -> Doc
<> String -> Doc
text String
comment Doc -> Doc -> Doc
<> Doc
newline)
| Bool
otherwise = Char -> Doc
char Char
'c' Doc -> Doc -> Doc
<> String -> Doc
text String
comment Doc -> Doc -> Doc
<> Doc
newline
endGen :: Pretty a => FortranVersion -> Doc -> a -> Indentation -> Doc
endGen :: FortranVersion -> Doc -> a -> Indentation -> Doc
endGen FortranVersion
v Doc
constructName a
name Indentation
i = Indentation -> Doc -> Doc
indent Indentation
i (Doc -> Doc) -> Doc -> Doc
forall a b. (a -> b) -> a -> b
$ Doc
"end" Doc -> Doc -> Doc
<+> Doc
middle Doc -> Doc -> Doc
<> Doc
newline
where
middle :: Doc
middle
| FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
< FortranVersion
Fortran77 = Doc
empty
| FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
< FortranVersion
Fortran90 = Doc
constructName
| Bool
otherwise = Doc
constructName Doc -> Doc -> Doc
<?+> FortranVersion -> a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v a
name
instance IndentablePretty [Block a] where
pprint :: FortranVersion -> [Block a] -> Indentation -> Doc
pprint FortranVersion
v [Block a]
bs Indentation
i = (Doc -> Block a -> Doc) -> Doc -> [Block a] -> Doc
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' (\Doc
b Block a
a -> Doc
b Doc -> Doc -> Doc
<> FortranVersion -> Block a -> Indentation -> Doc
forall t.
IndentablePretty t =>
FortranVersion -> t -> Indentation -> Doc
pprint FortranVersion
v Block a
a Indentation
i) Doc
empty [Block a]
bs
instance IndentablePretty (Block a) where
pprint :: FortranVersion -> Block a -> Indentation -> Doc
pprint FortranVersion
v (BlForall a
_ SrcSpan
_ Maybe (Expression a)
mLabel Maybe String
mName ForallHeader a
_ [Block a]
body Maybe (Expression a)
mel) Indentation
i =
Maybe (Expression a) -> Doc -> Doc
forall t. Pretty t => t -> Doc -> Doc
labeledIndent Maybe (Expression a)
mLabel (FortranVersion -> Maybe String -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Maybe String
mName) Doc -> Doc -> Doc
<> Doc
newline Doc -> Doc -> Doc
<>
FortranVersion -> [Block a] -> Indentation -> Doc
forall t.
IndentablePretty t =>
FortranVersion -> t -> Indentation -> Doc
pprint FortranVersion
v [Block a]
body Indentation
nextI Doc -> Doc -> Doc
<>
Maybe (Expression a) -> Doc -> Doc
forall t. Pretty t => t -> Doc -> Doc
labeledIndent Maybe (Expression a)
mel (Doc
"end forall" Doc -> Doc -> Doc
<+> FortranVersion -> Maybe String -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Maybe String
mName Doc -> Doc -> Doc
<> Doc
newline)
where
nextI :: Indentation
nextI = Indentation -> Indentation
incIndentation Indentation
i
labeledIndent :: t -> Doc -> Doc
labeledIndent t
label Doc
stDoc =
FortranVersion -> t -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v t
label Doc -> Doc -> Doc
`overlay` Indentation -> Doc -> Doc
indent Indentation
i Doc
stDoc
pprint FortranVersion
v (BlStatement a
_ SrcSpan
_ Maybe (Expression a)
mLabel Statement a
st) Indentation
i =
if FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= FortranVersion
Fortran90
then Indentation -> Doc -> Doc
indent Indentation
i (FortranVersion -> Maybe (Expression a) -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Maybe (Expression a)
mLabel Doc -> Doc -> Doc
<+> FortranVersion -> Statement a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Statement a
st Doc -> Doc -> Doc
<> Doc
newline)
else FortranVersion -> Maybe (Expression a) -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Maybe (Expression a)
mLabel Doc -> Doc -> Doc
`overlay` Indentation -> Doc -> Doc
indent Indentation
i (FortranVersion -> Statement a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Statement a
st Doc -> Doc -> Doc
<> Doc
newline)
pprint FortranVersion
v (BlIf a
_ SrcSpan
_ Maybe (Expression a)
mLabel Maybe String
mName [Maybe (Expression a)]
conds [[Block a]]
bodies Maybe (Expression a)
el) Indentation
i
| FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= FortranVersion
Fortran77 =
Maybe (Expression a) -> Doc -> Doc
forall t. Pretty t => t -> Doc -> Doc
labeledIndent Maybe (Expression a)
mLabel
(FortranVersion -> Maybe String -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Maybe String
mName Doc -> Doc -> Doc
<?> Doc
colon Doc -> Doc -> Doc
<+>
Doc
"if" Doc -> Doc -> Doc
<+> Doc -> Doc
parens (FortranVersion -> Maybe (Expression a) -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Maybe (Expression a)
firstCond) Doc -> Doc -> Doc
<+> Doc
"then" Doc -> Doc -> Doc
<> Doc
newline) Doc -> Doc -> Doc
<>
FortranVersion -> [Block a] -> Indentation -> Doc
forall t.
IndentablePretty t =>
FortranVersion -> t -> Indentation -> Doc
pprint FortranVersion
v [Block a]
firstBody Indentation
nextI Doc -> Doc -> Doc
<>
(Doc -> Doc -> Doc) -> Doc -> [Doc] -> Doc
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' Doc -> Doc -> Doc
(<>) Doc
empty (((Maybe (Expression a), [Block a]) -> Doc)
-> [(Maybe (Expression a), [Block a])] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map (Maybe (Expression a), [Block a]) -> Doc
forall t t. (Pretty t, IndentablePretty t) => (Maybe t, t) -> Doc
displayCondBlock [(Maybe (Expression a), [Block a])]
restCondsBodies) Doc -> Doc -> Doc
<>
Maybe (Expression a) -> Doc -> Doc
forall t. Pretty t => t -> Doc -> Doc
labeledIndent Maybe (Expression a)
el (Doc
"end if" Doc -> Doc -> Doc
<+> FortranVersion -> Maybe String -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Maybe String
mName Doc -> Doc -> Doc
<> Doc
newline)
| Bool
otherwise = FortranVersion -> String -> FortranVersion -> Doc
forall a. FortranVersion -> String -> FortranVersion -> a
tooOld FortranVersion
v String
"Structured if" FortranVersion
Fortran77
where
((Maybe (Expression a)
firstCond, [Block a]
firstBody): [(Maybe (Expression a), [Block a])]
restCondsBodies) = [Maybe (Expression a)]
-> [[Block a]] -> [(Maybe (Expression a), [Block a])]
forall a b. [a] -> [b] -> [(a, b)]
zip [Maybe (Expression a)]
conds [[Block a]]
bodies
displayCondBlock :: (Maybe t, t) -> Doc
displayCondBlock (Maybe t
mCond, t
block) =
Indentation -> Doc -> Doc
indent Indentation
i
(case Maybe t
mCond of {
Just t
cond -> Doc
"else if" Doc -> Doc -> Doc
<+> Doc -> Doc
parens (FortranVersion -> t -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v t
cond) Doc -> Doc -> Doc
<+> Doc
"then";
Maybe t
Nothing -> Doc
"else"
} Doc -> Doc -> Doc
<> Doc
newline) Doc -> Doc -> Doc
<>
FortranVersion -> t -> Indentation -> Doc
forall t.
IndentablePretty t =>
FortranVersion -> t -> Indentation -> Doc
pprint FortranVersion
v t
block Indentation
nextI
nextI :: Indentation
nextI = Indentation -> Indentation
incIndentation Indentation
i
labeledIndent :: t -> Doc -> Doc
labeledIndent t
label Doc
stDoc =
if FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= FortranVersion
Fortran90
then Indentation -> Doc -> Doc
indent Indentation
i (FortranVersion -> t -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v t
label Doc -> Doc -> Doc
<+> Doc
stDoc)
else FortranVersion -> Maybe (Expression a) -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Maybe (Expression a)
mLabel Doc -> Doc -> Doc
`overlay` Indentation -> Doc -> Doc
indent Indentation
i Doc
stDoc
pprint FortranVersion
v (BlCase a
_ SrcSpan
_ Maybe (Expression a)
mLabel Maybe String
mName Expression a
scrutinee [Maybe (AList Index a)]
ranges [[Block a]]
bodies Maybe (Expression a)
el) Indentation
i
| FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= FortranVersion
Fortran90 =
Indentation -> Doc -> Doc
indent Indentation
i
(FortranVersion -> Maybe (Expression a) -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Maybe (Expression a)
mLabel Doc -> Doc -> Doc
<+>
FortranVersion -> Maybe String -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Maybe String
mName Doc -> Doc -> Doc
<?> Doc
colon Doc -> Doc -> Doc
<+>
Doc
"select case" Doc -> Doc -> Doc
<+> Doc -> Doc
parens (FortranVersion -> Expression a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Expression a
scrutinee) Doc -> Doc -> Doc
<> Doc
newline) Doc -> Doc -> Doc
<>
(Doc -> Doc -> Doc) -> Doc -> [Doc] -> Doc
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' Doc -> Doc -> Doc
(<>) Doc
empty ((Maybe (AList Index a) -> [Block a] -> Doc)
-> [Maybe (AList Index a)] -> [[Block a]] -> [Doc]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith (((Maybe (AList Index a), [Block a]) -> Doc)
-> Maybe (AList Index a) -> [Block a] -> Doc
forall a b c. ((a, b) -> c) -> a -> b -> c
curry (Maybe (AList Index a), [Block a]) -> Doc
forall t t. (Pretty t, IndentablePretty t) => (Maybe t, t) -> Doc
displayRangeBlock) [Maybe (AList Index a)]
ranges [[Block a]]
bodies) Doc -> Doc -> Doc
<>
Indentation -> Doc -> Doc
indent Indentation
i (FortranVersion -> Maybe (Expression a) -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Maybe (Expression a)
el Doc -> Doc -> Doc
<+> Doc
"end select" Doc -> Doc -> Doc
<+> FortranVersion -> Maybe String -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Maybe String
mName Doc -> Doc -> Doc
<> Doc
newline)
| Bool
otherwise = FortranVersion -> String -> FortranVersion -> Doc
forall a. FortranVersion -> String -> FortranVersion -> a
tooOld FortranVersion
v String
"Select case" FortranVersion
Fortran90
where
displayRangeBlock :: (Maybe t, t) -> Doc
displayRangeBlock (Maybe t
mRanges, t
block) =
Indentation -> Doc -> Doc
indent Indentation
nextI
(Doc
"case" Doc -> Doc -> Doc
<+>
case Maybe t
mRanges of {
Just t
ranges' -> Doc -> Doc
parens (FortranVersion -> t -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v t
ranges');
Maybe t
Nothing -> Doc
"default" } Doc -> Doc -> Doc
<> Doc
newline) Doc -> Doc -> Doc
<>
FortranVersion -> t -> Indentation -> Doc
forall t.
IndentablePretty t =>
FortranVersion -> t -> Indentation -> Doc
pprint FortranVersion
v t
block (Indentation -> Indentation
incIndentation Indentation
nextI)
nextI :: Indentation
nextI = Indentation -> Indentation
incIndentation Indentation
i
pprint FortranVersion
v (BlInterface a
_ SrcSpan
_ Maybe (Expression a)
mLabel Bool
abstractp [ProgramUnit a]
pus [Block a]
moduleProcs) Indentation
i
| FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= FortranVersion
Fortran90 =
Indentation -> Doc -> Doc
indent Indentation
i (Doc
abstract Doc -> Doc -> Doc
<> Doc
"interface" Doc -> Doc -> Doc
<+> FortranVersion -> Maybe (Expression a) -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Maybe (Expression a)
mLabel Doc -> Doc -> Doc
<> Doc
newline) Doc -> Doc -> Doc
<>
FortranVersion -> [ProgramUnit a] -> Indentation -> Doc
forall t.
IndentablePretty t =>
FortranVersion -> t -> Indentation -> Doc
pprint FortranVersion
v [ProgramUnit a]
pus Indentation
nextI Doc -> Doc -> Doc
<>
Doc
newline Doc -> Doc -> Doc
<>
FortranVersion -> [Block a] -> Indentation -> Doc
forall t.
IndentablePretty t =>
FortranVersion -> t -> Indentation -> Doc
pprint FortranVersion
v [Block a]
moduleProcs Indentation
nextI Doc -> Doc -> Doc
<>
Indentation -> Doc -> Doc
indent Indentation
i (Doc
"end interface" Doc -> Doc -> Doc
<> Doc
newline)
| Bool
otherwise = FortranVersion -> String -> FortranVersion -> Doc
forall a. FortranVersion -> String -> FortranVersion -> a
tooOld FortranVersion
v String
"Interface" FortranVersion
Fortran90
where
nextI :: Indentation
nextI = Indentation -> Indentation
incIndentation Indentation
i
abstract :: Doc
abstract | FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= FortranVersion
Fortran2003 Bool -> Bool -> Bool
&& Bool
abstractp = Doc
"abstract "
| Bool
otherwise = Doc
empty
pprint FortranVersion
v (BlDo a
_ SrcSpan
_ Maybe (Expression a)
mLabel Maybe String
mn Maybe (Expression a)
tl Maybe (DoSpecification a)
doSpec [Block a]
body Maybe (Expression a)
el) Indentation
i
| FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= FortranVersion
Fortran77Extended =
Maybe (Expression a) -> Doc -> Doc
forall t. Pretty t => t -> Doc -> Doc
labeledIndent Maybe (Expression a)
mLabel
(FortranVersion -> Maybe String -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Maybe String
mn Doc -> Doc -> Doc
<?> Doc
colon Doc -> Doc -> Doc
<+>
Doc
"do" Doc -> Doc -> Doc
<+> FortranVersion -> Maybe (Expression a) -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Maybe (Expression a)
tl Doc -> Doc -> Doc
<+> FortranVersion -> Maybe (DoSpecification a) -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Maybe (DoSpecification a)
doSpec Doc -> Doc -> Doc
<> Doc
newline) Doc -> Doc -> Doc
<>
FortranVersion -> [Block a] -> Indentation -> Doc
forall t.
IndentablePretty t =>
FortranVersion -> t -> Indentation -> Doc
pprint FortranVersion
v [Block a]
body Indentation
nextI Doc -> Doc -> Doc
<>
if Maybe (Expression a) -> Bool
forall a. Maybe a -> Bool
isJust Maybe (Expression a)
tl Bool -> Bool -> Bool
&& Maybe String -> Bool
forall a. Maybe a -> Bool
isNothing Maybe String
mn
then Doc
empty
else Maybe (Expression a) -> Doc -> Doc
forall t. Pretty t => t -> Doc -> Doc
labeledIndent Maybe (Expression a)
el (Doc
"end do" Doc -> Doc -> Doc
<+> FortranVersion -> Maybe String -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Maybe String
mn Doc -> Doc -> Doc
<> Doc
newline)
| Bool
otherwise =
case Maybe (Expression a)
tl of
Just Expression a
tLabel ->
Maybe (Expression a) -> Doc -> Doc
forall t. Pretty t => t -> Doc -> Doc
labeledIndent Maybe (Expression a)
mLabel
(Doc
"do" Doc -> Doc -> Doc
<+> FortranVersion -> Expression a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Expression a
tLabel Doc -> Doc -> Doc
<+> FortranVersion -> Maybe (DoSpecification a) -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Maybe (DoSpecification a)
doSpec Doc -> Doc -> Doc
<> Doc
newline) Doc -> Doc -> Doc
<>
FortranVersion -> [Block a] -> Indentation -> Doc
forall t.
IndentablePretty t =>
FortranVersion -> t -> Indentation -> Doc
pprint FortranVersion
v [Block a]
body Indentation
nextI
Maybe (Expression a)
Nothing ->
String -> Doc
forall a. HasCallStack => String -> a
error String
"Fortran 77 and earlier versions only have labeled DO blocks"
where
nextI :: Indentation
nextI = Indentation -> Indentation
incIndentation Indentation
i
labeledIndent :: t -> Doc -> Doc
labeledIndent t
label Doc
stDoc =
if FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= FortranVersion
Fortran90
then Indentation -> Doc -> Doc
indent Indentation
i (FortranVersion -> t -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v t
label Doc -> Doc -> Doc
<+> Doc
stDoc)
else FortranVersion -> Maybe (Expression a) -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Maybe (Expression a)
mLabel Doc -> Doc -> Doc
`overlay` Indentation -> Doc -> Doc
indent Indentation
i Doc
stDoc
pprint FortranVersion
v (BlDoWhile a
_ SrcSpan
_ Maybe (Expression a)
mLabel Maybe String
mName Maybe (Expression a)
mTarget Expression a
cond [Block a]
body Maybe (Expression a)
el) Indentation
i
| FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= FortranVersion
Fortran77Extended =
Maybe (Expression a) -> Doc -> Doc
forall t. Pretty t => t -> Doc -> Doc
labeledIndent Maybe (Expression a)
mLabel
(FortranVersion -> Maybe String -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Maybe String
mName Doc -> Doc -> Doc
<?> Doc
colon Doc -> Doc -> Doc
<+>
Doc
"do" Doc -> Doc -> Doc
<+> FortranVersion -> Maybe (Expression a) -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Maybe (Expression a)
mTarget Doc -> Doc -> Doc
<+> Doc
"while" Doc -> Doc -> Doc
<+> Doc -> Doc
parens (FortranVersion -> Expression a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Expression a
cond) Doc -> Doc -> Doc
<> Doc
newline) Doc -> Doc -> Doc
<>
FortranVersion -> [Block a] -> Indentation -> Doc
forall t.
IndentablePretty t =>
FortranVersion -> t -> Indentation -> Doc
pprint FortranVersion
v [Block a]
body Indentation
nextI Doc -> Doc -> Doc
<>
if Maybe (Expression a) -> Bool
forall a. Maybe a -> Bool
isJust Maybe (Expression a)
mTarget Bool -> Bool -> Bool
&& Maybe String -> Bool
forall a. Maybe a -> Bool
isNothing Maybe String
mName
then Doc
empty
else Maybe (Expression a) -> Doc -> Doc
forall t. Pretty t => t -> Doc -> Doc
labeledIndent Maybe (Expression a)
el (Doc
"end do" Doc -> Doc -> Doc
<+> FortranVersion -> Maybe String -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Maybe String
mName Doc -> Doc -> Doc
<> Doc
newline)
| Bool
otherwise = FortranVersion -> String -> FortranVersion -> Doc
forall a. FortranVersion -> String -> FortranVersion -> a
tooOld FortranVersion
v String
"Do while loop" FortranVersion
Fortran77Extended
where
nextI :: Indentation
nextI = Indentation -> Indentation
incIndentation Indentation
i
labeledIndent :: t -> Doc -> Doc
labeledIndent t
label Doc
stDoc =
if FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= FortranVersion
Fortran90
then Indentation -> Doc -> Doc
indent Indentation
i (FortranVersion -> t -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v t
label Doc -> Doc -> Doc
<+> Doc
stDoc)
else FortranVersion -> Maybe (Expression a) -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Maybe (Expression a)
mLabel Doc -> Doc -> Doc
`overlay` Indentation -> Doc -> Doc
indent Indentation
i Doc
stDoc
pprint FortranVersion
v (BlComment a
_ SrcSpan
_ (Comment String
comment)) Indentation
i
| FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= FortranVersion
Fortran90 = Indentation -> Doc -> Doc
indent Indentation
i (Char -> Doc
char Char
'!' Doc -> Doc -> Doc
<> String -> Doc
text String
comment Doc -> Doc -> Doc
<> Doc
newline)
| Bool
otherwise = Char -> Doc
char Char
'c' Doc -> Doc -> Doc
<> String -> Doc
text String
comment Doc -> Doc -> Doc
<> Doc
newline
class Pretty t where
pprint' :: FortranVersion -> t -> Doc
instance Pretty a => Pretty (Maybe a) where
pprint' :: FortranVersion -> Maybe a -> Doc
pprint' FortranVersion
_ Maybe a
Nothing = Doc
empty
pprint' FortranVersion
v (Just a
e) = FortranVersion -> a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v a
e
instance Pretty String where
pprint' :: FortranVersion -> String -> Doc
pprint' FortranVersion
_ = String -> Doc
text
instance Pretty (e a) => Pretty (AList e a) where
pprint' :: FortranVersion -> AList e a -> Doc
pprint' FortranVersion
v AList e a
es = [Doc] -> Doc
commaSep ((e a -> Doc) -> [e a] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map (FortranVersion -> e a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v) (AList e a -> [e a]
forall (t :: * -> *) a. AList t a -> [t a]
aStrip AList e a
es))
instance Pretty BaseType where
pprint' :: FortranVersion -> BaseType -> Doc
pprint' FortranVersion
_ BaseType
TypeInteger = Doc
"integer"
pprint' FortranVersion
_ BaseType
TypeReal = Doc
"real"
pprint' FortranVersion
_ BaseType
TypeDoublePrecision = Doc
"double precision"
pprint' FortranVersion
_ BaseType
TypeComplex = Doc
"complex"
pprint' FortranVersion
v BaseType
TypeDoubleComplex
| FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Eq a => a -> a -> Bool
== FortranVersion
Fortran77Extended = Doc
"double complex"
| Bool
otherwise = FortranVersion -> String -> FortranVersion -> Doc
forall a. FortranVersion -> String -> FortranVersion -> a
tooOld FortranVersion
v String
"Double complex" FortranVersion
Fortran77Extended
pprint' FortranVersion
_ BaseType
TypeLogical = Doc
"logical"
pprint' FortranVersion
v (TypeCharacter Maybe CharacterLen
_ Maybe String
_)
| FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= FortranVersion
Fortran77 = Doc
"character"
| Bool
otherwise = FortranVersion -> String -> FortranVersion -> Doc
forall a. FortranVersion -> String -> FortranVersion -> a
tooOld FortranVersion
v String
"Character data type" FortranVersion
Fortran77
pprint' FortranVersion
v (TypeCustom String
str)
| FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= FortranVersion
Fortran90 = Doc
"type" Doc -> Doc -> Doc
<+> Doc -> Doc
parens (String -> Doc
text String
str)
| FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= FortranVersion
Fortran77Extended = Doc
"record" Doc -> Doc -> Doc
<+> Char -> Doc
char Char
'/' Doc -> Doc -> Doc
<> String -> Doc
text String
str Doc -> Doc -> Doc
<> Char -> Doc
char Char
'/'
| Bool
otherwise = FortranVersion -> String -> FortranVersion -> Doc
forall a. FortranVersion -> String -> FortranVersion -> a
tooOld FortranVersion
v String
"User defined type" FortranVersion
Fortran90
pprint' FortranVersion
v BaseType
TypeByte
| FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= FortranVersion
Fortran77Extended = Doc
"byte"
| Bool
otherwise = FortranVersion -> String -> FortranVersion -> Doc
forall a. FortranVersion -> String -> FortranVersion -> a
tooOld FortranVersion
v String
"Byte" FortranVersion
Fortran77Extended
pprint' FortranVersion
v BaseType
ClassStar
| FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= FortranVersion
Fortran2003 = Doc
"class(*)"
| Bool
otherwise = FortranVersion -> String -> FortranVersion -> Doc
forall a. FortranVersion -> String -> FortranVersion -> a
tooOld FortranVersion
v String
"Class(*)" FortranVersion
Fortran2003
pprint' FortranVersion
v (ClassCustom String
str)
| FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= FortranVersion
Fortran2003 = Doc
"class" Doc -> Doc -> Doc
<> Doc -> Doc
parens (String -> Doc
text String
str)
| Bool
otherwise = FortranVersion -> String -> FortranVersion -> Doc
forall a. FortranVersion -> String -> FortranVersion -> a
tooOld FortranVersion
v String
"Class(spec)" FortranVersion
Fortran2003
instance Pretty CharacterLen where
pprint' :: FortranVersion -> CharacterLen -> Doc
pprint' FortranVersion
_ CharacterLen
CharLenStar = Doc
"*"
pprint' FortranVersion
_ CharacterLen
CharLenColon = Doc
":"
pprint' FortranVersion
_ CharacterLen
CharLenExp = Doc
"*"
pprint' FortranVersion
_ (CharLenInt Int
i) = String -> Doc
text (Int -> String
forall a. Show a => a -> String
show Int
i)
instance Pretty (TypeSpec a) where
pprint' :: FortranVersion -> TypeSpec a -> Doc
pprint' FortranVersion
v (TypeSpec a
_ SrcSpan
_ BaseType
baseType Maybe (Selector a)
mSelector) =
FortranVersion -> BaseType -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v BaseType
baseType Doc -> Doc -> Doc
<> FortranVersion -> Maybe (Selector a) -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Maybe (Selector a)
mSelector
instance Pretty (Selector a) where
pprint' :: FortranVersion -> Selector a -> Doc
pprint' FortranVersion
v (Selector a
_ SrcSpan
_ Maybe (Expression a)
mLenSel Maybe (Expression a)
mKindSel)
| FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
< FortranVersion
Fortran77 = FortranVersion -> String -> FortranVersion -> Doc
forall a. FortranVersion -> String -> FortranVersion -> a
tooOld FortranVersion
v String
"Length/kind selector" FortranVersion
Fortran77
| FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
< FortranVersion
Fortran90 =
case (Maybe (Expression a)
mLenSel, Maybe (Expression a)
mKindSel) of
(Just Expression a
lenSel, Maybe (Expression a)
Nothing) ->
Char -> Doc
char Char
'*' Doc -> Doc -> Doc
<> Expression a -> Doc
forall a. Expression a -> Doc
noParensLit Expression a
lenSel
(Maybe (Expression a)
Nothing, Just Expression a
kindSel) ->
Char -> Doc
char Char
'*' Doc -> Doc -> Doc
<> Expression a -> Doc
forall a. Expression a -> Doc
noParensLit Expression a
kindSel
(Maybe (Expression a), Maybe (Expression a))
_ -> String -> Doc
forall a. HasCallStack => String -> a
error String
"Kind and length selectors can be active one at a time in\
\Fortran 77."
| FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= FortranVersion
Fortran90 =
case (Maybe (Expression a)
mLenSel, Maybe (Expression a)
mKindSel) of
(Just Expression a
lenSel, Just Expression a
kindSel) ->
Doc -> Doc
parens (Doc -> Doc) -> Doc -> Doc
forall a b. (a -> b) -> a -> b
$ Expression a -> Doc
forall t. Pretty t => t -> Doc
len Expression a
lenSel Doc -> Doc -> Doc
<> Char -> Doc
char Char
',' Doc -> Doc -> Doc
<+> Expression a -> Doc
forall t. Pretty t => t -> Doc
kind Expression a
kindSel
(Maybe (Expression a)
Nothing, Just Expression a
kindSel) -> Doc -> Doc
parens (Doc -> Doc) -> Doc -> Doc
forall a b. (a -> b) -> a -> b
$ Expression a -> Doc
forall t. Pretty t => t -> Doc
kind Expression a
kindSel
(Just Expression a
lenDev, Maybe (Expression a)
Nothing) -> Doc -> Doc
parens (Doc -> Doc) -> Doc -> Doc
forall a b. (a -> b) -> a -> b
$ Expression a -> Doc
forall t. Pretty t => t -> Doc
len Expression a
lenDev
(Maybe (Expression a), Maybe (Expression a))
_ -> String -> Doc
forall a. HasCallStack => String -> a
error String
"No way for both kind and length selectors to be empty in \
\Fortran 90 onwards."
| Bool
otherwise = String -> Doc
forall a. HasCallStack => String -> a
error String
"unhandled version"
where
len :: t -> Doc
len t
e = Doc
"len=" Doc -> Doc -> Doc
<> FortranVersion -> t -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v t
e
kind :: t -> Doc
kind t
e = Doc
"kind=" Doc -> Doc -> Doc
<> FortranVersion -> t -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v t
e
noParensLit :: Expression a -> Doc
noParensLit e :: Expression a
e@(ExpValue a
_ SrcSpan
_ (ValInteger String
_)) = FortranVersion -> Expression a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Expression a
e
noParensLit Expression a
e = Doc -> Doc
parens (Doc -> Doc) -> Doc -> Doc
forall a b. (a -> b) -> a -> b
$ FortranVersion -> Expression a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Expression a
e
instance Pretty (Statement a) where
pprint' :: FortranVersion -> Statement a -> Doc
pprint' FortranVersion
v (StDeclaration a
_ SrcSpan
_ TypeSpec a
typeSpec Maybe (AList Attribute a)
mAttrList AList Declarator a
declList)
| FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
< FortranVersion
Fortran90 = FortranVersion -> TypeSpec a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v TypeSpec a
typeSpec Doc -> Doc -> Doc
<+> FortranVersion -> AList Declarator a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v AList Declarator a
declList
| FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= FortranVersion
Fortran90 =
FortranVersion -> TypeSpec a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v TypeSpec a
typeSpec Doc -> Doc -> Doc
<>
(if Maybe (AList Attribute a) -> Bool
forall a. Maybe a -> Bool
isJust Maybe (AList Attribute a)
mAttrList then Doc
comma else Doc
empty) Doc -> Doc -> Doc
<+>
FortranVersion -> Maybe (AList Attribute a) -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Maybe (AList Attribute a)
mAttrList Doc -> Doc -> Doc
<+>
String -> Doc
text String
"::" Doc -> Doc -> Doc
<+>
FortranVersion -> AList Declarator a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v AList Declarator a
declList
| Bool
otherwise = String -> Doc
forall a. HasCallStack => String -> a
error String
"unhandled version"
pprint' FortranVersion
v (StStructure a
_ SrcSpan
_ Maybe String
mName AList StructureItem a
itemList)
| FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Eq a => a -> a -> Bool
/= FortranVersion
Fortran77Extended = FortranVersion -> String -> FortranVersion -> Doc
forall a. FortranVersion -> String -> FortranVersion -> a
tooOld FortranVersion
v String
"Structure" FortranVersion
Fortran77Extended
| Bool
otherwise =
Doc
"structure" Doc -> Doc -> Doc
<> (if Maybe String -> Bool
forall a. Maybe a -> Bool
isJust Maybe String
mName then Doc
" /" Doc -> Doc -> Doc
<> FortranVersion -> Maybe String -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Maybe String
mName Doc -> Doc -> Doc
<> Doc
"/" else Doc
empty) Doc -> Doc -> Doc
<> Doc
newline Doc -> Doc -> Doc
<>
(Doc -> StructureItem a -> Doc) -> Doc -> [StructureItem a] -> Doc
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' (\Doc
doc StructureItem a
item -> Doc
doc Doc -> Doc -> Doc
<> FortranVersion -> StructureItem a -> Indentation -> Doc
forall t.
IndentablePretty t =>
FortranVersion -> t -> Indentation -> Doc
pprint FortranVersion
v StructureItem a
item (Indentation -> Indentation
incIndentation (Int -> Indentation
forall a. a -> Maybe a
Just Int
0)) Doc -> Doc -> Doc
<> Doc
newline) Doc
empty (AList StructureItem a -> [StructureItem a]
forall (t :: * -> *) a. AList t a -> [t a]
aStrip AList StructureItem a
itemList) Doc -> Doc -> Doc
<>
Doc
"end structure"
pprint' FortranVersion
v (StIntent a
_ SrcSpan
_ Intent
intent AList Expression a
exps)
| FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= FortranVersion
Fortran90 =
Doc
"intent" Doc -> Doc -> Doc
<+> Doc -> Doc
parens (FortranVersion -> Intent -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Intent
intent) Doc -> Doc -> Doc
<+> Doc
"::" Doc -> Doc -> Doc
<+> FortranVersion -> AList Expression a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v AList Expression a
exps
| Bool
otherwise = FortranVersion -> String -> FortranVersion -> Doc
forall a. FortranVersion -> String -> FortranVersion -> a
tooOld FortranVersion
v String
"Intent statement" FortranVersion
Fortran90
pprint' FortranVersion
v (StOptional a
_ SrcSpan
_ AList Expression a
vars)
| FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= FortranVersion
Fortran90 = Doc
"optional ::" Doc -> Doc -> Doc
<+> FortranVersion -> AList Expression a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v AList Expression a
vars
| Bool
otherwise = FortranVersion -> String -> FortranVersion -> Doc
forall a. FortranVersion -> String -> FortranVersion -> a
tooOld FortranVersion
v String
"Optional statement" FortranVersion
Fortran90
pprint' FortranVersion
v (StPublic a
_ SrcSpan
_ Maybe (AList Expression a)
mVars)
| FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= FortranVersion
Fortran90 = Doc
"public" Doc -> Doc -> Doc
<> Doc
" :: " Doc -> Doc -> Doc
<?> FortranVersion -> Maybe (AList Expression a) -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Maybe (AList Expression a)
mVars
| Bool
otherwise = FortranVersion -> String -> FortranVersion -> Doc
forall a. FortranVersion -> String -> FortranVersion -> a
tooOld FortranVersion
v String
"Public statement" FortranVersion
Fortran90
pprint' FortranVersion
v (StPrivate a
_ SrcSpan
_ Maybe (AList Expression a)
mVars)
| FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= FortranVersion
Fortran90 = Doc
"private" Doc -> Doc -> Doc
<> Doc
" :: " Doc -> Doc -> Doc
<?> FortranVersion -> Maybe (AList Expression a) -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Maybe (AList Expression a)
mVars
| Bool
otherwise = FortranVersion -> String -> FortranVersion -> Doc
forall a. FortranVersion -> String -> FortranVersion -> a
tooOld FortranVersion
v String
"Private statement" FortranVersion
Fortran90
pprint' FortranVersion
v (StProtected a
_ SrcSpan
_ Maybe (AList Expression a)
mVars)
| FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= FortranVersion
Fortran2003 = Doc
"protected" Doc -> Doc -> Doc
<> Doc
" :: " Doc -> Doc -> Doc
<?> FortranVersion -> Maybe (AList Expression a) -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Maybe (AList Expression a)
mVars
| Bool
otherwise = FortranVersion -> String -> FortranVersion -> Doc
forall a. FortranVersion -> String -> FortranVersion -> a
tooOld FortranVersion
v String
"Protected statement" FortranVersion
Fortran2003
pprint' FortranVersion
v (StSave a
_ SrcSpan
_ Maybe (AList Expression a)
mVars)
| FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= FortranVersion
Fortran90 = Doc
"save" Doc -> Doc -> Doc
<> Doc
" :: " Doc -> Doc -> Doc
<?> FortranVersion -> Maybe (AList Expression a) -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Maybe (AList Expression a)
mVars
| Bool
otherwise = Doc
"save" Doc -> Doc -> Doc
<+> FortranVersion -> Maybe (AList Expression a) -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Maybe (AList Expression a)
mVars
pprint' FortranVersion
v (StDimension a
_ SrcSpan
_ AList Declarator a
decls)
| FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= FortranVersion
Fortran90 = Doc
"dimension ::" Doc -> Doc -> Doc
<+> FortranVersion -> AList Declarator a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v AList Declarator a
decls
| Bool
otherwise = Doc
"dimension" Doc -> Doc -> Doc
<+> FortranVersion -> AList Declarator a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v AList Declarator a
decls
pprint' FortranVersion
v (StAllocatable a
_ SrcSpan
_ AList Declarator a
decls)
| FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= FortranVersion
Fortran90 = Doc
"allocatable ::" Doc -> Doc -> Doc
<+> FortranVersion -> AList Declarator a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v AList Declarator a
decls
| Bool
otherwise = FortranVersion -> String -> FortranVersion -> Doc
forall a. FortranVersion -> String -> FortranVersion -> a
tooOld FortranVersion
v String
"Allocatable statement" FortranVersion
Fortran90
pprint' FortranVersion
v (StAsynchronous a
_ SrcSpan
_ AList Declarator a
decls)
| FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= FortranVersion
Fortran2003 = Doc
"asynchronous ::" Doc -> Doc -> Doc
<+> FortranVersion -> AList Declarator a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v AList Declarator a
decls
| Bool
otherwise = FortranVersion -> String -> FortranVersion -> Doc
forall a. FortranVersion -> String -> FortranVersion -> a
tooOld FortranVersion
v String
"Asynchronous statement" FortranVersion
Fortran2003
pprint' FortranVersion
v (StPointer a
_ SrcSpan
_ AList Declarator a
decls)
| FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= FortranVersion
Fortran90 = Doc
"pointer ::" Doc -> Doc -> Doc
<+> FortranVersion -> AList Declarator a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v AList Declarator a
decls
| Bool
otherwise = FortranVersion -> String -> FortranVersion -> Doc
forall a. FortranVersion -> String -> FortranVersion -> a
tooOld FortranVersion
v String
"Pointer statement" FortranVersion
Fortran90
pprint' FortranVersion
v (StTarget a
_ SrcSpan
_ AList Declarator a
decls)
| FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= FortranVersion
Fortran90 = Doc
"target ::" Doc -> Doc -> Doc
<+> FortranVersion -> AList Declarator a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v AList Declarator a
decls
| Bool
otherwise = FortranVersion -> String -> FortranVersion -> Doc
forall a. FortranVersion -> String -> FortranVersion -> a
tooOld FortranVersion
v String
"Target statement" FortranVersion
Fortran90
pprint' FortranVersion
v (StValue a
_ SrcSpan
_ AList Declarator a
decls)
| FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= FortranVersion
Fortran95 = Doc
"value ::" Doc -> Doc -> Doc
<+> FortranVersion -> AList Declarator a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v AList Declarator a
decls
| Bool
otherwise = FortranVersion -> String -> FortranVersion -> Doc
forall a. FortranVersion -> String -> FortranVersion -> a
tooOld FortranVersion
v String
"Value statement" FortranVersion
Fortran95
pprint' FortranVersion
v (StVolatile a
_ SrcSpan
_ AList Declarator a
decls)
| FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= FortranVersion
Fortran95 = Doc
"volatile ::" Doc -> Doc -> Doc
<+> FortranVersion -> AList Declarator a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v AList Declarator a
decls
| Bool
otherwise = FortranVersion -> String -> FortranVersion -> Doc
forall a. FortranVersion -> String -> FortranVersion -> a
tooOld FortranVersion
v String
"Volatile statement" FortranVersion
Fortran95
pprint' FortranVersion
v (StData a
_ SrcSpan
_ aDataGroups :: AList DataGroup a
aDataGroups@(AList a
_ SrcSpan
_ [DataGroup a]
dataGroups))
| FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= FortranVersion
Fortran90 = Doc
"data" Doc -> Doc -> Doc
<+> FortranVersion -> AList DataGroup a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v AList DataGroup a
aDataGroups
| Bool
otherwise = Doc
"data" Doc -> Doc -> Doc
<+> [Doc] -> Doc
hsep ((DataGroup a -> Doc) -> [DataGroup a] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map (FortranVersion -> DataGroup a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v) [DataGroup a]
dataGroups)
pprint' FortranVersion
v (StAutomatic a
_ SrcSpan
_ AList Declarator a
decls)
| FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Eq a => a -> a -> Bool
== FortranVersion
Fortran77Extended = Doc
"automatic" Doc -> Doc -> Doc
<+> FortranVersion -> AList Declarator a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v AList Declarator a
decls
| Bool
otherwise = FortranVersion -> String -> FortranVersion -> Doc
forall a. FortranVersion -> String -> FortranVersion -> a
tooOld FortranVersion
v String
"Automatic statement" FortranVersion
Fortran90
pprint' FortranVersion
v (StNamelist a
_ SrcSpan
_ AList Namelist a
namelist)
| FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= FortranVersion
Fortran90 = Doc
"namelist" Doc -> Doc -> Doc
<+> FortranVersion -> AList Namelist a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v AList Namelist a
namelist
| Bool
otherwise = FortranVersion -> String -> FortranVersion -> Doc
forall a. FortranVersion -> String -> FortranVersion -> a
tooOld FortranVersion
v String
"Namelist statement" FortranVersion
Fortran90
pprint' FortranVersion
v (StParameter a
_ SrcSpan
_ AList Declarator a
aDecls) = Doc
"parameter" Doc -> Doc -> Doc
<+> Doc -> Doc
parens (FortranVersion -> AList Declarator a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v AList Declarator a
aDecls)
pprint' FortranVersion
v (StExternal a
_ SrcSpan
_ AList Expression a
vars) = Doc
"external" Doc -> Doc -> Doc
<+> FortranVersion -> AList Expression a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v AList Expression a
vars
pprint' FortranVersion
v (StIntrinsic a
_ SrcSpan
_ AList Expression a
vars) = Doc
"intrinsic" Doc -> Doc -> Doc
<+> FortranVersion -> AList Expression a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v AList Expression a
vars
pprint' FortranVersion
v (StCommon a
_ SrcSpan
_ AList CommonGroup a
aCommonGroups) = Doc
"common" Doc -> Doc -> Doc
<+> FortranVersion -> AList CommonGroup a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v AList CommonGroup a
aCommonGroups
pprint' FortranVersion
v (StEquivalence a
_ SrcSpan
_ (AList a
_ SrcSpan
_ [AList Expression a]
equivGroups)) =
Doc
"equivalence" Doc -> Doc -> Doc
<+> [Doc] -> Doc
commaSep ((AList Expression a -> Doc) -> [AList Expression a] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map (Doc -> Doc
parens (Doc -> Doc)
-> (AList Expression a -> Doc) -> AList Expression a -> Doc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FortranVersion -> AList Expression a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v) [AList Expression a]
equivGroups)
pprint' FortranVersion
v (StFormat a
_ SrcSpan
_ (AList a
_ SrcSpan
_ [FormatItem a]
formatItems)) =
Doc
"format" Doc -> Doc -> Doc
<+> [Doc] -> Doc
hcat ((FormatItem a -> Doc) -> [FormatItem a] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map (FortranVersion -> FormatItem a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v) [FormatItem a]
formatItems)
pprint' FortranVersion
v (StImplicit a
_ SrcSpan
_ Maybe (AList ImpList a)
mImpLists)
| Just AList ImpList a
impLists <- Maybe (AList ImpList a)
mImpLists = Doc
"implicit" Doc -> Doc -> Doc
<+> FortranVersion -> AList ImpList a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v AList ImpList a
impLists
| Bool
otherwise = Doc
"implicit none"
pprint' FortranVersion
v (StEntry a
_ SrcSpan
_ Expression a
name Maybe (AList Expression a)
mArgs Maybe (Expression a)
mResult)
| FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
< FortranVersion
Fortran90 =
case Maybe (Expression a)
mResult of
Maybe (Expression a)
Nothing ->
Doc
"entry" Doc -> Doc -> Doc
<+> FortranVersion -> Expression a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Expression a
name Doc -> Doc -> Doc
<+> Doc -> Doc
parens (FortranVersion -> Maybe (AList Expression a) -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Maybe (AList Expression a)
mArgs)
Just Expression a
_ -> FortranVersion -> String -> FortranVersion -> Doc
forall a. FortranVersion -> String -> FortranVersion -> a
tooOld FortranVersion
v String
"Explicit result" FortranVersion
Fortran90
| Bool
otherwise =
Doc
"entry" Doc -> Doc -> Doc
<+>
FortranVersion -> Expression a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Expression a
name Doc -> Doc -> Doc
<+> Doc -> Doc
parens (FortranVersion -> Maybe (AList Expression a) -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Maybe (AList Expression a)
mArgs) Doc -> Doc -> Doc
<+>
Doc
"result (" Doc -> Doc -> Doc
<?> FortranVersion -> Maybe (Expression a) -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Maybe (Expression a)
mResult Doc -> Doc -> Doc
<?> Char -> Doc
char Char
')'
pprint' FortranVersion
v (StInclude a
_ SrcSpan
_ Expression a
file Maybe [Block a]
_) = Doc
"include" Doc -> Doc -> Doc
<+> FortranVersion -> Expression a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Expression a
file
pprint' FortranVersion
v (StDo a
_ SrcSpan
_ Maybe String
mConstructor Maybe (Expression a)
mLabel Maybe (DoSpecification a)
mDoSpec)
| FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
< FortranVersion
Fortran90
, Just String
_ <- Maybe String
mConstructor = FortranVersion -> String -> FortranVersion -> Doc
forall a. FortranVersion -> String -> FortranVersion -> a
tooOld FortranVersion
v String
"Named DO block" FortranVersion
Fortran90
| FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
< FortranVersion
Fortran77Extended
, Maybe (Expression a)
Nothing <- Maybe (Expression a)
mLabel = FortranVersion -> String -> FortranVersion -> Doc
forall a. FortranVersion -> String -> FortranVersion -> a
tooOld FortranVersion
v String
"Labelless DO block" FortranVersion
Fortran90
| FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
< FortranVersion
Fortran90
, Maybe (DoSpecification a)
Nothing <- Maybe (DoSpecification a)
mDoSpec = FortranVersion -> String -> FortranVersion -> Doc
forall a. FortranVersion -> String -> FortranVersion -> a
tooOld FortranVersion
v String
"Infinite DO loop" FortranVersion
Fortran90
| Bool
otherwise =
FortranVersion -> Maybe String -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Maybe String
mConstructor Doc -> Doc -> Doc
<?> Doc
colon Doc -> Doc -> Doc
<+>
Doc
"do" Doc -> Doc -> Doc
<+> FortranVersion -> Maybe (Expression a) -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Maybe (Expression a)
mLabel Doc -> Doc -> Doc
<+> FortranVersion -> Maybe (DoSpecification a) -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Maybe (DoSpecification a)
mDoSpec
pprint' FortranVersion
v (StDoWhile a
_ SrcSpan
_ Maybe String
mConstructor Maybe (Expression a)
mLabel Expression a
pred)
| FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
< FortranVersion
Fortran77Extended = FortranVersion -> String -> FortranVersion -> Doc
forall a. FortranVersion -> String -> FortranVersion -> a
tooOld FortranVersion
v String
"While loop" FortranVersion
Fortran77Extended
| Bool
otherwise =
FortranVersion -> Maybe String -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Maybe String
mConstructor Doc -> Doc -> Doc
<?> Doc
colon Doc -> Doc -> Doc
<+>
Doc
"do" Doc -> Doc -> Doc
<+> FortranVersion -> Maybe (Expression a) -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Maybe (Expression a)
mLabel Doc -> Doc -> Doc
<+>
Doc
"while" Doc -> Doc -> Doc
<+> Doc -> Doc
parens (FortranVersion -> Expression a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Expression a
pred)
pprint' FortranVersion
v (StEnddo a
_ SrcSpan
_ Maybe String
mConstructor)
| FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
< FortranVersion
Fortran77Extended = FortranVersion -> String -> FortranVersion -> Doc
forall a. FortranVersion -> String -> FortranVersion -> a
tooOld FortranVersion
v String
"End do" FortranVersion
Fortran77Extended
| FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
< FortranVersion
Fortran90
, Maybe String
_ <- Maybe String
mConstructor = FortranVersion -> String -> FortranVersion -> Doc
forall a. FortranVersion -> String -> FortranVersion -> a
tooOld FortranVersion
v String
"Named DO loop" FortranVersion
Fortran90
| Bool
otherwise = Doc
"end do" Doc -> Doc -> Doc
<+> FortranVersion -> Maybe String -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Maybe String
mConstructor
pprint' FortranVersion
v (StExpressionAssign a
_ SrcSpan
_ Expression a
lhs Expression a
rhs) =
FortranVersion -> Expression a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Expression a
lhs Doc -> Doc -> Doc
<+> Doc
equals Doc -> Doc -> Doc
<+> FortranVersion -> Expression a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Expression a
rhs
pprint' FortranVersion
v (StCycle a
_ SrcSpan
_ Maybe (Expression a)
mConstructor)
| FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= FortranVersion
Fortran90 = Doc
"cycle" Doc -> Doc -> Doc
<+> FortranVersion -> Maybe (Expression a) -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Maybe (Expression a)
mConstructor
| Bool
otherwise = FortranVersion -> String -> FortranVersion -> Doc
forall a. FortranVersion -> String -> FortranVersion -> a
tooOld FortranVersion
v String
"Cycle" FortranVersion
Fortran90
pprint' FortranVersion
v (StExit a
_ SrcSpan
_ Maybe (Expression a)
mConstructor)
| FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= FortranVersion
Fortran77Extended = Doc
"exit" Doc -> Doc -> Doc
<+> FortranVersion -> Maybe (Expression a) -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Maybe (Expression a)
mConstructor
| Bool
otherwise = FortranVersion -> String -> FortranVersion -> Doc
forall a. FortranVersion -> String -> FortranVersion -> a
tooOld FortranVersion
v String
"Exit" FortranVersion
Fortran77Extended
pprint' FortranVersion
v (StIfLogical a
_ SrcSpan
_ Expression a
pred Statement a
st) =
Doc
"if" Doc -> Doc -> Doc
<+> Doc -> Doc
parens (FortranVersion -> Expression a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Expression a
pred) Doc -> Doc -> Doc
<+> FortranVersion -> Statement a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Statement a
st
pprint' FortranVersion
v (StIfArithmetic a
_ SrcSpan
_ Expression a
exp Expression a
ltPred Expression a
eqPred Expression a
gtPred) =
Doc
"if" Doc -> Doc -> Doc
<+> Doc -> Doc
parens (FortranVersion -> Expression a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Expression a
exp) Doc -> Doc -> Doc
<+>
FortranVersion -> Expression a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Expression a
ltPred Doc -> Doc -> Doc
<> Doc
comma Doc -> Doc -> Doc
<+>
FortranVersion -> Expression a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Expression a
eqPred Doc -> Doc -> Doc
<> Doc
comma Doc -> Doc -> Doc
<+>
FortranVersion -> Expression a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Expression a
gtPred
pprint' FortranVersion
v (StIfThen a
_ SrcSpan
_ Maybe String
mConstructor Expression a
condition)
| FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= FortranVersion
Fortran90 =
FortranVersion -> Maybe String -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Maybe String
mConstructor Doc -> Doc -> Doc
<?> Doc
colon Doc -> Doc -> Doc
<+>
Doc
"if" Doc -> Doc -> Doc
<+> Doc -> Doc
parens (FortranVersion -> Expression a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Expression a
condition) Doc -> Doc -> Doc
<+> Doc
"then"
| FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= FortranVersion
Fortran77Extended =
case Maybe String
mConstructor of
Maybe String
Nothing -> Doc
"if" Doc -> Doc -> Doc
<+> Doc -> Doc
parens (FortranVersion -> Expression a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Expression a
condition) Doc -> Doc -> Doc
<+> Doc
"then"
Maybe String
_ -> FortranVersion -> String -> FortranVersion -> Doc
forall a. FortranVersion -> String -> FortranVersion -> a
tooOld FortranVersion
v String
"Else" FortranVersion
Fortran77Extended
| Bool
otherwise = FortranVersion -> String -> FortranVersion -> Doc
forall a. FortranVersion -> String -> FortranVersion -> a
tooOld FortranVersion
v String
"Structured if" FortranVersion
Fortran90
pprint' FortranVersion
v (StElse a
_ SrcSpan
_ Maybe String
mConstructor)
| FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= FortranVersion
Fortran90 = Doc
"else" Doc -> Doc -> Doc
<+> FortranVersion -> Maybe String -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Maybe String
mConstructor
| FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= FortranVersion
Fortran77Extended =
case Maybe String
mConstructor of
Maybe String
Nothing -> Doc
"else"
Just String
_ -> FortranVersion -> String -> FortranVersion -> Doc
forall a. FortranVersion -> String -> FortranVersion -> a
tooOld FortranVersion
v String
"Named else" FortranVersion
Fortran90
| Bool
otherwise = FortranVersion -> String -> FortranVersion -> Doc
forall a. FortranVersion -> String -> FortranVersion -> a
tooOld FortranVersion
v String
"Else" FortranVersion
Fortran77Extended
pprint' FortranVersion
v (StElsif a
_ SrcSpan
_ Maybe String
mConstructor Expression a
condition)
| FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= FortranVersion
Fortran90 =
Doc
"else if" Doc -> Doc -> Doc
<+> Doc -> Doc
parens (FortranVersion -> Expression a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Expression a
condition) Doc -> Doc -> Doc
<+> FortranVersion -> Maybe String -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Maybe String
mConstructor
| FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= FortranVersion
Fortran77Extended =
case Maybe String
mConstructor of
Maybe String
Nothing -> Doc
"else if" Doc -> Doc -> Doc
<+> Doc -> Doc
parens (FortranVersion -> Expression a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Expression a
condition)
Maybe String
_ -> FortranVersion -> String -> FortranVersion -> Doc
forall a. FortranVersion -> String -> FortranVersion -> a
tooOld FortranVersion
v String
"Named else if" FortranVersion
Fortran90
| Bool
otherwise = FortranVersion -> String -> FortranVersion -> Doc
forall a. FortranVersion -> String -> FortranVersion -> a
tooOld FortranVersion
v String
"Else if" FortranVersion
Fortran77Extended
pprint' FortranVersion
v (StEndif a
_ SrcSpan
_ Maybe String
mConstructor)
| FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= FortranVersion
Fortran90 = Doc
"end if" Doc -> Doc -> Doc
<+> FortranVersion -> Maybe String -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Maybe String
mConstructor
| FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= FortranVersion
Fortran77Extended =
case Maybe String
mConstructor of
Maybe String
Nothing -> Doc
"end if"
Just String
_ -> FortranVersion -> String -> FortranVersion -> Doc
forall a. FortranVersion -> String -> FortranVersion -> a
tooOld FortranVersion
v String
"Named end if" FortranVersion
Fortran90
| Bool
otherwise = FortranVersion -> String -> FortranVersion -> Doc
forall a. FortranVersion -> String -> FortranVersion -> a
tooOld FortranVersion
v String
"End if" FortranVersion
Fortran77Extended
pprint' FortranVersion
v (StSelectCase a
_ SrcSpan
_ Maybe String
mConstructor Expression a
exp)
| FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= FortranVersion
Fortran90 =
FortranVersion -> Maybe String -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Maybe String
mConstructor Doc -> Doc -> Doc
<?> Doc
colon Doc -> Doc -> Doc
<+>
Doc
"select case" Doc -> Doc -> Doc
<+> Doc -> Doc
parens (FortranVersion -> Expression a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Expression a
exp)
| Bool
otherwise = FortranVersion -> String -> FortranVersion -> Doc
forall a. FortranVersion -> String -> FortranVersion -> a
tooOld FortranVersion
v String
"Case statement" FortranVersion
Fortran90
pprint' FortranVersion
v (StCase a
_ SrcSpan
_ Maybe String
mConstructor Maybe (AList Index a)
mCase)
| FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= FortranVersion
Fortran90 =
case Maybe (AList Index a)
mCase of
Just AList Index a
casee ->
Doc
"case" Doc -> Doc -> Doc
<+> Doc -> Doc
parens (FortranVersion -> AList Index a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v AList Index a
casee) Doc -> Doc -> Doc
<+> FortranVersion -> Maybe String -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Maybe String
mConstructor
Maybe (AList Index a)
Nothing -> Doc
"case default" Doc -> Doc -> Doc
<+> FortranVersion -> Maybe String -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Maybe String
mConstructor
| Bool
otherwise = FortranVersion -> String -> FortranVersion -> Doc
forall a. FortranVersion -> String -> FortranVersion -> a
tooOld FortranVersion
v String
"Case statement" FortranVersion
Fortran90
pprint' FortranVersion
v (StEndcase a
_ SrcSpan
_ Maybe String
mConstructor)
| FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= FortranVersion
Fortran90 = Doc
"end case" Doc -> Doc -> Doc
<+> FortranVersion -> Maybe String -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Maybe String
mConstructor
| Bool
otherwise = FortranVersion -> String -> FortranVersion -> Doc
forall a. FortranVersion -> String -> FortranVersion -> a
tooOld FortranVersion
v String
"Case statement" FortranVersion
Fortran90
pprint' FortranVersion
v (StFunction a
_ SrcSpan
_ Expression a
name AList Expression a
args Expression a
rhs) =
FortranVersion -> Expression a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Expression a
name Doc -> Doc -> Doc
<> Doc -> Doc
parens (FortranVersion -> AList Expression a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v AList Expression a
args) Doc -> Doc -> Doc
<+> Doc
equals Doc -> Doc -> Doc
<+> FortranVersion -> Expression a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Expression a
rhs
pprint' FortranVersion
v (StPointerAssign a
_ SrcSpan
_ Expression a
lhs Expression a
rhs)
| FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= FortranVersion
Fortran90 = FortranVersion -> Expression a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Expression a
lhs Doc -> Doc -> Doc
<+> Doc
"=>" Doc -> Doc -> Doc
<+> FortranVersion -> Expression a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Expression a
rhs
| Bool
otherwise = FortranVersion -> String -> FortranVersion -> Doc
forall a. FortranVersion -> String -> FortranVersion -> a
tooOld FortranVersion
v String
"Pointer assignment" FortranVersion
Fortran90
pprint' FortranVersion
v (StLabelAssign a
_ SrcSpan
_ Expression a
label Expression a
binding) =
Doc
"assign" Doc -> Doc -> Doc
<+> FortranVersion -> Expression a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Expression a
label Doc -> Doc -> Doc
<+> Doc
"to" Doc -> Doc -> Doc
<+> FortranVersion -> Expression a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Expression a
binding
pprint' FortranVersion
v (StGotoUnconditional a
_ SrcSpan
_ Expression a
label) = Doc
"goto" Doc -> Doc -> Doc
<+> FortranVersion -> Expression a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Expression a
label
pprint' FortranVersion
v (StGotoAssigned a
_ SrcSpan
_ Expression a
target Maybe (AList Expression a)
labels) =
Doc
"goto" Doc -> Doc -> Doc
<+> FortranVersion -> Expression a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Expression a
target Doc -> Doc -> Doc
<+> Doc -> Doc
parens (FortranVersion -> Maybe (AList Expression a) -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Maybe (AList Expression a)
labels)
pprint' FortranVersion
v (StGotoComputed a
_ SrcSpan
_ AList Expression a
labels Expression a
target) =
Doc
"goto" Doc -> Doc -> Doc
<+> Doc -> Doc
parens (FortranVersion -> AList Expression a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v AList Expression a
labels) Doc -> Doc -> Doc
<+> FortranVersion -> Expression a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Expression a
target
pprint' FortranVersion
v (StCall a
_ SrcSpan
_ Expression a
name Maybe (AList Argument a)
args) = FortranVersion -> Expression a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Expression a
name Doc -> Doc -> Doc
<+> Doc -> Doc
parens (FortranVersion -> Maybe (AList Argument a) -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Maybe (AList Argument a)
args)
pprint' FortranVersion
_ (StContinue a
_ SrcSpan
_) = Doc
"continue"
pprint' FortranVersion
v (StReturn a
_ SrcSpan
_ Maybe (Expression a)
exp) = Doc
"return" Doc -> Doc -> Doc
<+> FortranVersion -> Maybe (Expression a) -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Maybe (Expression a)
exp
pprint' FortranVersion
v (StStop a
_ SrcSpan
_ Maybe (Expression a)
code) = Doc
"stop" Doc -> Doc -> Doc
<+> FortranVersion -> Maybe (Expression a) -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Maybe (Expression a)
code
pprint' FortranVersion
v (StPause a
_ SrcSpan
_ Maybe (Expression a)
code) = Doc
"pause" Doc -> Doc -> Doc
<+> FortranVersion -> Maybe (Expression a) -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Maybe (Expression a)
code
pprint' FortranVersion
v (StRead a
_ SrcSpan
_ AList ControlPair a
cilist Maybe (AList Expression a)
mIolist) =
Doc
"read" Doc -> Doc -> Doc
<+> Doc -> Doc
parens (FortranVersion -> AList ControlPair a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v AList ControlPair a
cilist) Doc -> Doc -> Doc
<+> FortranVersion -> Maybe (AList Expression a) -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Maybe (AList Expression a)
mIolist
pprint' FortranVersion
v (StRead2 a
_ SrcSpan
_ Expression a
formatId Maybe (AList Expression a)
mIolist) =
Doc
"read" Doc -> Doc -> Doc
<+> FortranVersion -> Expression a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Expression a
formatId Doc -> Doc -> Doc
<> Doc
comma Doc -> Doc -> Doc
<?+> FortranVersion -> Maybe (AList Expression a) -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Maybe (AList Expression a)
mIolist
pprint' FortranVersion
v (StWrite a
_ SrcSpan
_ AList ControlPair a
cilist Maybe (AList Expression a)
mIolist) =
Doc
"write" Doc -> Doc -> Doc
<+> Doc -> Doc
parens (FortranVersion -> AList ControlPair a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v AList ControlPair a
cilist) Doc -> Doc -> Doc
<+> FortranVersion -> Maybe (AList Expression a) -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Maybe (AList Expression a)
mIolist
pprint' FortranVersion
v (StPrint a
_ SrcSpan
_ Expression a
formatId Maybe (AList Expression a)
mIolist) =
Doc
"print" Doc -> Doc -> Doc
<+> FortranVersion -> Expression a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Expression a
formatId Doc -> Doc -> Doc
<> Doc
comma Doc -> Doc -> Doc
<?+> FortranVersion -> Maybe (AList Expression a) -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Maybe (AList Expression a)
mIolist
pprint' FortranVersion
v (StTypePrint a
_ SrcSpan
_ Expression a
formatId Maybe (AList Expression a)
mIolist)
| FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Eq a => a -> a -> Bool
== FortranVersion
Fortran77Extended
= Doc
"type" Doc -> Doc -> Doc
<+> FortranVersion -> Expression a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Expression a
formatId Doc -> Doc -> Doc
<> Doc
comma Doc -> Doc -> Doc
<?+> FortranVersion -> Maybe (AList Expression a) -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Maybe (AList Expression a)
mIolist
| Bool
otherwise = FortranVersion -> String -> FortranVersion -> Doc
forall a. FortranVersion -> String -> FortranVersion -> a
tooOld FortranVersion
v String
"Type (print) statement" FortranVersion
Fortran77Extended
pprint' FortranVersion
v (StOpen a
_ SrcSpan
_ AList ControlPair a
cilist) = Doc
"open" Doc -> Doc -> Doc
<+> Doc -> Doc
parens (FortranVersion -> AList ControlPair a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v AList ControlPair a
cilist)
pprint' FortranVersion
v (StClose a
_ SrcSpan
_ AList ControlPair a
cilist) = Doc
"close" Doc -> Doc -> Doc
<+> Doc -> Doc
parens (FortranVersion -> AList ControlPair a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v AList ControlPair a
cilist)
pprint' FortranVersion
v (StFlush a
_ SrcSpan
_ (AList a
_ SrcSpan
_ [FlushSpec a]
fslist))
| FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= FortranVersion
Fortran2003 = Doc
"flush" Doc -> Doc -> Doc
<+> Doc -> Doc
parens ([Doc] -> Doc
commaSep ([Doc] -> Doc) -> [Doc] -> Doc
forall a b. (a -> b) -> a -> b
$ (FlushSpec a -> Doc) -> [FlushSpec a] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map (FortranVersion -> FlushSpec a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v) [FlushSpec a]
fslist)
| Bool
otherwise = FortranVersion -> String -> FortranVersion -> Doc
forall a. FortranVersion -> String -> FortranVersion -> a
tooOld FortranVersion
v String
"Flush statement" FortranVersion
Fortran2003
pprint' FortranVersion
v (StInquire a
_ SrcSpan
_ AList ControlPair a
cilist) = Doc
"inquire" Doc -> Doc -> Doc
<+> Doc -> Doc
parens (FortranVersion -> AList ControlPair a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v AList ControlPair a
cilist)
pprint' FortranVersion
v (StRewind a
_ SrcSpan
_ AList ControlPair a
cilist) = Doc
"rewind" Doc -> Doc -> Doc
<+> Doc -> Doc
parens (FortranVersion -> AList ControlPair a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v AList ControlPair a
cilist)
pprint' FortranVersion
v (StRewind2 a
_ SrcSpan
_ Expression a
unit) = Doc
"rewind" Doc -> Doc -> Doc
<+> FortranVersion -> Expression a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Expression a
unit
pprint' FortranVersion
v (StBackspace a
_ SrcSpan
_ AList ControlPair a
cilist) =
Doc
"backspace" Doc -> Doc -> Doc
<+> Doc -> Doc
parens (FortranVersion -> AList ControlPair a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v AList ControlPair a
cilist)
pprint' FortranVersion
v (StBackspace2 a
_ SrcSpan
_ Expression a
unit) = Doc
"backspace" Doc -> Doc -> Doc
<+> FortranVersion -> Expression a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Expression a
unit
pprint' FortranVersion
v (StEndfile a
_ SrcSpan
_ AList ControlPair a
cilist) = Doc
"endfile" Doc -> Doc -> Doc
<+> Doc -> Doc
parens (FortranVersion -> AList ControlPair a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v AList ControlPair a
cilist)
pprint' FortranVersion
v (StEndfile2 a
_ SrcSpan
_ Expression a
unit) = Doc
"endfile" Doc -> Doc -> Doc
<+> FortranVersion -> Expression a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Expression a
unit
pprint' FortranVersion
v (StAllocate a
_ SrcSpan
_ (Just TypeSpec a
ty) AList Expression a
vars Maybe (AList AllocOpt a)
opts)
| FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= FortranVersion
Fortran2003 =
Doc
"allocate" Doc -> Doc -> Doc
<+> Doc -> Doc
parens (FortranVersion -> TypeSpec a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v TypeSpec a
ty Doc -> Doc -> Doc
<+> Doc
"::" Doc -> Doc -> Doc
<+> FortranVersion -> AList Expression a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v AList Expression a
vars Doc -> Doc -> Doc
<> Doc
comma Doc -> Doc -> Doc
<?+> FortranVersion -> Maybe (AList AllocOpt a) -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Maybe (AList AllocOpt a)
opts)
| Bool
otherwise = FortranVersion -> String -> FortranVersion -> Doc
forall a. FortranVersion -> String -> FortranVersion -> a
tooOld FortranVersion
v String
"Allocate with type_spec" FortranVersion
Fortran2003
pprint' FortranVersion
v (StAllocate a
_ SrcSpan
_ Maybe (TypeSpec a)
Nothing AList Expression a
vars Maybe (AList AllocOpt a)
opts)
| FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= FortranVersion
Fortran90 =
Doc
"allocate" Doc -> Doc -> Doc
<+> Doc -> Doc
parens (FortranVersion -> AList Expression a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v AList Expression a
vars Doc -> Doc -> Doc
<> Doc
comma Doc -> Doc -> Doc
<?+> FortranVersion -> Maybe (AList AllocOpt a) -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Maybe (AList AllocOpt a)
opts)
| Bool
otherwise = FortranVersion -> String -> FortranVersion -> Doc
forall a. FortranVersion -> String -> FortranVersion -> a
tooOld FortranVersion
v String
"Allocate" FortranVersion
Fortran90
pprint' FortranVersion
v (StDeallocate a
_ SrcSpan
_ AList Expression a
vars Maybe (AList AllocOpt a)
opts)
| FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= FortranVersion
Fortran90 =
Doc
"deallocate" Doc -> Doc -> Doc
<+> Doc -> Doc
parens (FortranVersion -> AList Expression a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v AList Expression a
vars Doc -> Doc -> Doc
<> Doc
comma Doc -> Doc -> Doc
<?+> FortranVersion -> Maybe (AList AllocOpt a) -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Maybe (AList AllocOpt a)
opts)
| Bool
otherwise = FortranVersion -> String -> FortranVersion -> Doc
forall a. FortranVersion -> String -> FortranVersion -> a
tooOld FortranVersion
v String
"Deallocate" FortranVersion
Fortran90
pprint' FortranVersion
v (StNullify a
_ SrcSpan
_ AList Expression a
vars) = Doc
"nullify" Doc -> Doc -> Doc
<+> FortranVersion -> AList Expression a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v AList Expression a
vars
pprint' FortranVersion
v (StWhere a
_ SrcSpan
_ Expression a
mask Statement a
assignment)
| FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= FortranVersion
Fortran90 =
Doc
"where" Doc -> Doc -> Doc
<+> Doc -> Doc
parens (FortranVersion -> Expression a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Expression a
mask) Doc -> Doc -> Doc
<+> FortranVersion -> Statement a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Statement a
assignment
| Bool
otherwise = FortranVersion -> String -> FortranVersion -> Doc
forall a. FortranVersion -> String -> FortranVersion -> a
tooOld FortranVersion
v String
"Where statement" FortranVersion
Fortran90
pprint' FortranVersion
v (StWhereConstruct a
_ SrcSpan
_ (Just String
lab) Expression a
mask)
| FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= FortranVersion
Fortran2003 = String -> Doc
text String
lab Doc -> Doc -> Doc
<> Doc
":" Doc -> Doc -> Doc
<+> Doc
"where" Doc -> Doc -> Doc
<+> Doc -> Doc
parens (FortranVersion -> Expression a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Expression a
mask)
| Bool
otherwise = FortranVersion -> String -> FortranVersion -> Doc
forall a. FortranVersion -> String -> FortranVersion -> a
tooOld FortranVersion
v String
"Labelled where construct" FortranVersion
Fortran2003
pprint' FortranVersion
v (StWhereConstruct a
_ SrcSpan
_ Maybe String
Nothing Expression a
mask)
| FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= FortranVersion
Fortran90 = Doc
"where" Doc -> Doc -> Doc
<+> Doc -> Doc
parens (FortranVersion -> Expression a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Expression a
mask)
| Bool
otherwise = FortranVersion -> String -> FortranVersion -> Doc
forall a. FortranVersion -> String -> FortranVersion -> a
tooOld FortranVersion
v String
"Where construct" FortranVersion
Fortran90
pprint' FortranVersion
v (StElsewhere a
_ SrcSpan
_ (Just String
lab) Maybe (Expression a)
mexp)
| FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= FortranVersion
Fortran2003 = Doc
"else where" Doc -> Doc -> Doc
<+> Doc
"(" Doc -> Doc -> Doc
<?> FortranVersion -> Maybe (Expression a) -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Maybe (Expression a)
mexp Doc -> Doc -> Doc
<?> Doc
")" Doc -> Doc -> Doc
<+> String -> Doc
text String
lab
| Bool
otherwise = FortranVersion -> String -> FortranVersion -> Doc
forall a. FortranVersion -> String -> FortranVersion -> a
tooOld FortranVersion
v String
"Labelled ELSEWHERE" FortranVersion
Fortran2003
pprint' FortranVersion
v (StElsewhere a
_ SrcSpan
_ Maybe String
Nothing Maybe (Expression a)
mexp)
| FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= FortranVersion
Fortran90 = Doc
"else where" Doc -> Doc -> Doc
<+> Doc
"(" Doc -> Doc -> Doc
<?> FortranVersion -> Maybe (Expression a) -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Maybe (Expression a)
mexp Doc -> Doc -> Doc
<?> Doc
")"
| Bool
otherwise = FortranVersion -> String -> FortranVersion -> Doc
forall a. FortranVersion -> String -> FortranVersion -> a
tooOld FortranVersion
v String
"Else where" FortranVersion
Fortran90
pprint' FortranVersion
v (StEndWhere a
_ SrcSpan
_ (Just String
lab))
| FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= FortranVersion
Fortran2003 = Doc
"end where" Doc -> Doc -> Doc
<+> String -> Doc
text String
lab
| Bool
otherwise = FortranVersion -> String -> FortranVersion -> Doc
forall a. FortranVersion -> String -> FortranVersion -> a
tooOld FortranVersion
v String
"Labelled END WHERE" FortranVersion
Fortran2003
pprint' FortranVersion
v (StEndWhere a
_ SrcSpan
_ Maybe String
Nothing)
| FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= FortranVersion
Fortran90 = Doc
"end where"
| Bool
otherwise = FortranVersion -> String -> FortranVersion -> Doc
forall a. FortranVersion -> String -> FortranVersion -> a
tooOld FortranVersion
v String
"End where" FortranVersion
Fortran90
pprint' FortranVersion
v (StUse a
_ SrcSpan
_ Expression a
moduleName Maybe ModuleNature
mIntrinsic Only
only Maybe (AList Use a)
mappings)
| FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= FortranVersion
Fortran2003 =
Doc
"use" Doc -> Doc -> Doc
<> (Doc
comma Doc -> Doc -> Doc
<?+> Doc
intrinsic Doc -> Doc -> Doc
<?+> Doc
"::") Doc -> Doc -> Doc
<+> FortranVersion -> Expression a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Expression a
moduleName Doc -> Doc -> Doc
<>
(Doc
comma Doc -> Doc -> Doc
<?+> (FortranVersion -> Only -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Only
only Doc -> Doc -> Doc
<+> FortranVersion -> Maybe (AList Use a) -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Maybe (AList Use a)
mappings))
| FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= FortranVersion
Fortran90 =
Doc
"use" Doc -> Doc -> Doc
<+> FortranVersion -> Expression a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Expression a
moduleName Doc -> Doc -> Doc
<>
(Doc
comma Doc -> Doc -> Doc
<?+> (FortranVersion -> Only -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Only
only Doc -> Doc -> Doc
<+> FortranVersion -> Maybe (AList Use a) -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Maybe (AList Use a)
mappings))
| Bool
otherwise = FortranVersion -> String -> FortranVersion -> Doc
forall a. FortranVersion -> String -> FortranVersion -> a
tooOld FortranVersion
v String
"Module system" FortranVersion
Fortran90
where
intrinsic :: Doc
intrinsic = case Maybe ModuleNature
mIntrinsic of
Just ModuleNature
ModIntrinsic -> Doc
"intrinsic"
Just ModuleNature
ModNonIntrinsic -> Doc
"non_intrinsic"
Maybe ModuleNature
Nothing -> Doc
empty
pprint' FortranVersion
v (StModuleProcedure a
_ SrcSpan
_ AList Expression a
procedures)
| FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= FortranVersion
Fortran90 =
Doc
"module procedure" Doc -> Doc -> Doc
<+> FortranVersion -> AList Expression a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v AList Expression a
procedures
| Bool
otherwise = FortranVersion -> String -> FortranVersion -> Doc
forall a. FortranVersion -> String -> FortranVersion -> a
tooOld FortranVersion
v String
"Module procedure" FortranVersion
Fortran90
pprint' FortranVersion
v (StProcedure a
_ SrcSpan
_ Maybe (ProcInterface a)
mProcInterface Maybe (Attribute a)
mSuffix (AList a
_ SrcSpan
_ [ProcDecl a]
procDecls))
| FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= FortranVersion
Fortran2003 =
Doc
"procedure" Doc -> Doc -> Doc
<> Doc -> Doc
parens (FortranVersion -> Maybe (ProcInterface a) -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Maybe (ProcInterface a)
mProcInterface) Doc -> Doc -> Doc
<>
Doc
comma Doc -> Doc -> Doc
<?+> FortranVersion -> Maybe (Attribute a) -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Maybe (Attribute a)
mSuffix Doc -> Doc -> Doc
<+> Doc
"::" Doc -> Doc -> Doc
<?+>
[Doc] -> Doc
commaSep ((ProcDecl a -> Doc) -> [ProcDecl a] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map (FortranVersion -> ProcDecl a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v) [ProcDecl a]
procDecls)
| Bool
otherwise = FortranVersion -> String -> FortranVersion -> Doc
forall a. FortranVersion -> String -> FortranVersion -> a
tooOld FortranVersion
v String
"Procedure" FortranVersion
Fortran2003
pprint' FortranVersion
v (StType a
_ SrcSpan
_ Maybe (AList Attribute a)
attrs String
name)
| FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= FortranVersion
Fortran90 = Doc
"type" Doc -> Doc -> Doc
<+> FortranVersion -> Maybe (AList Attribute a) -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Maybe (AList Attribute a)
attrs Doc -> Doc -> Doc
<+> FortranVersion -> String -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v String
name
| Bool
otherwise = FortranVersion -> String -> FortranVersion -> Doc
forall a. FortranVersion -> String -> FortranVersion -> a
tooOld FortranVersion
v String
"Derived type" FortranVersion
Fortran90
pprint' FortranVersion
v (StEndType a
_ SrcSpan
_ Maybe String
name)
| FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= FortranVersion
Fortran90 = Doc
"end type" Doc -> Doc -> Doc
<+> FortranVersion -> Maybe String -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Maybe String
name
| Bool
otherwise = FortranVersion -> String -> FortranVersion -> Doc
forall a. FortranVersion -> String -> FortranVersion -> a
tooOld FortranVersion
v String
"Derived type" FortranVersion
Fortran90
pprint' FortranVersion
v (StEnum a
_ SrcSpan
_)
| FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= FortranVersion
Fortran2003 = Doc
"enum, bind(c)"
| Bool
otherwise = FortranVersion -> String -> FortranVersion -> Doc
forall a. FortranVersion -> String -> FortranVersion -> a
tooOld FortranVersion
v String
"Enum" FortranVersion
Fortran2003
pprint' FortranVersion
v (StEnumerator a
_ SrcSpan
_ AList Declarator a
decls)
| FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= FortranVersion
Fortran2003 = Doc
"enumerator ::" Doc -> Doc -> Doc
<+> FortranVersion -> AList Declarator a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v AList Declarator a
decls
| Bool
otherwise = FortranVersion -> String -> FortranVersion -> Doc
forall a. FortranVersion -> String -> FortranVersion -> a
tooOld FortranVersion
v String
"Enumator" FortranVersion
Fortran2003
pprint' FortranVersion
v (StEndEnum a
_ SrcSpan
_)
| FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= FortranVersion
Fortran2003 = Doc
"end enum"
| Bool
otherwise = FortranVersion -> String -> FortranVersion -> Doc
forall a. FortranVersion -> String -> FortranVersion -> a
tooOld FortranVersion
v String
"End enum" FortranVersion
Fortran2003
pprint' FortranVersion
v (StSequence a
_ SrcSpan
_)
| FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= FortranVersion
Fortran90 = Doc
"sequence"
| Bool
otherwise = FortranVersion -> String -> FortranVersion -> Doc
forall a. FortranVersion -> String -> FortranVersion -> a
tooOld FortranVersion
v String
"Sequence" FortranVersion
Fortran90
pprint' FortranVersion
v (StImport a
_ SrcSpan
_ (AList a
_ SrcSpan
_ [Expression a]
vs))
| FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= FortranVersion
Fortran2003 = Doc
"import" Doc -> Doc -> Doc
<+> [Doc] -> Doc
commaSep ((Expression a -> Doc) -> [Expression a] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map (FortranVersion -> Expression a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v) [Expression a]
vs)
| Bool
otherwise = FortranVersion -> String -> FortranVersion -> Doc
forall a. FortranVersion -> String -> FortranVersion -> a
tooOld FortranVersion
v String
"Import" FortranVersion
Fortran2003
pprint' FortranVersion
v (StFormatBogus a
_ SrcSpan
_ String
blob) = Doc
"format" Doc -> Doc -> Doc
<+> FortranVersion -> String -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v String
blob
pprint' FortranVersion
_ StForall{} = String -> Doc
forall a. HasCallStack => String -> a
error String
"unhandled pprint StForall"
pprint' FortranVersion
_ StForallStatement{} = String -> Doc
forall a. HasCallStack => String -> a
error String
"unhandled pprint StForallStatement"
pprint' FortranVersion
_ StEndForall{} = String -> Doc
forall a. HasCallStack => String -> a
error String
"unhandled pprint StEndForall"
instance Pretty (ProcInterface a) where
pprint' :: FortranVersion -> ProcInterface a -> Doc
pprint' FortranVersion
v (ProcInterfaceName a
_ SrcSpan
_ Expression a
e) = FortranVersion -> Expression a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Expression a
e
pprint' FortranVersion
v (ProcInterfaceType a
_ SrcSpan
_ TypeSpec a
t) = FortranVersion -> TypeSpec a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v TypeSpec a
t
instance Pretty (ProcDecl a) where
pprint' :: FortranVersion -> ProcDecl a -> Doc
pprint' FortranVersion
v (ProcDecl a
_ SrcSpan
_ Expression a
e1 (Just Expression a
e2)) = FortranVersion -> Expression a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Expression a
e1 Doc -> Doc -> Doc
<+> Doc
"=>" Doc -> Doc -> Doc
<+> FortranVersion -> Expression a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Expression a
e2
pprint' FortranVersion
v (ProcDecl a
_ SrcSpan
_ Expression a
e1 Maybe (Expression a)
Nothing) = FortranVersion -> Expression a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Expression a
e1
instance Pretty Only where
pprint' :: FortranVersion -> Only -> Doc
pprint' FortranVersion
_ Only
Exclusive = Doc
"only" Doc -> Doc -> Doc
<> Doc
colon
pprint' FortranVersion
_ Only
Permissive = Doc
empty
instance Pretty (Use a) where
pprint' :: FortranVersion -> Use a -> Doc
pprint' FortranVersion
v Use a
use
| FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= FortranVersion
Fortran90 =
case Use a
use of
UseRename a
_ SrcSpan
_ Expression a
uSrc Expression a
uDst -> FortranVersion -> Expression a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Expression a
uSrc Doc -> Doc -> Doc
<+> Doc
"=>" Doc -> Doc -> Doc
<+> FortranVersion -> Expression a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Expression a
uDst
UseID a
_ SrcSpan
_ Expression a
u -> FortranVersion -> Expression a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Expression a
u
| FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
< FortranVersion
Fortran90 = FortranVersion -> String -> FortranVersion -> Doc
forall a. FortranVersion -> String -> FortranVersion -> a
tooOld FortranVersion
v String
"Module system" FortranVersion
Fortran90
| Bool
otherwise = String -> Doc
forall a. HasCallStack => String -> a
error String
"unhandled version"
instance Pretty (Argument a) where
pprint' :: FortranVersion -> Argument a -> Doc
pprint' FortranVersion
v (Argument a
_ SrcSpan
_ Maybe String
key Expression a
e) =
case Maybe String
key of
Just String
keyName -> String -> Doc
text String
keyName Doc -> Doc -> Doc
<+> Char -> Doc
char Char
'=' Doc -> Doc -> Doc
<+> FortranVersion -> Expression a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Expression a
e
Maybe String
Nothing -> FortranVersion -> Expression a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Expression a
e
instance Pretty (Attribute a) where
pprint' :: FortranVersion -> Attribute a -> Doc
pprint' FortranVersion
v Attribute a
attr
| FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= FortranVersion
Fortran90 =
case Attribute a
attr of
AttrAsynchronous a
_ SrcSpan
_
| FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= FortranVersion
Fortran2003 -> Doc
"asynchronous"
| Bool
otherwise -> FortranVersion -> String -> FortranVersion -> Doc
forall a. FortranVersion -> String -> FortranVersion -> a
tooOld FortranVersion
v String
"Asynchronous attribute" FortranVersion
Fortran2003
AttrValue a
_ SrcSpan
_
| FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= FortranVersion
Fortran95 -> Doc
"value"
| Bool
otherwise -> FortranVersion -> String -> FortranVersion -> Doc
forall a. FortranVersion -> String -> FortranVersion -> a
tooOld FortranVersion
v String
"Value attribute" FortranVersion
Fortran95
AttrVolatile a
_ SrcSpan
_
| FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= FortranVersion
Fortran95 -> Doc
"volatile"
| Bool
otherwise -> FortranVersion -> String -> FortranVersion -> Doc
forall a. FortranVersion -> String -> FortranVersion -> a
tooOld FortranVersion
v String
"Volatile attribute" FortranVersion
Fortran95
AttrSuffix a
_ SrcSpan
_ Suffix a
s
| FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= FortranVersion
Fortran2003 -> FortranVersion -> Suffix a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Suffix a
s
| Bool
otherwise -> FortranVersion -> String -> FortranVersion -> Doc
forall a. FortranVersion -> String -> FortranVersion -> a
tooOld FortranVersion
v String
"Bind (language-binding-spec) attribute" FortranVersion
Fortran2003
AttrParameter a
_ SrcSpan
_ -> Doc
"parameter"
AttrPublic a
_ SrcSpan
_ -> Doc
"public"
AttrPrivate a
_ SrcSpan
_ -> Doc
"private"
AttrProtected a
_ SrcSpan
_
| FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= FortranVersion
Fortran2003 -> Doc
"protected"
| Bool
otherwise -> FortranVersion -> String -> FortranVersion -> Doc
forall a. FortranVersion -> String -> FortranVersion -> a
tooOld FortranVersion
v String
"Protected attribute" FortranVersion
Fortran2003
AttrAllocatable a
_ SrcSpan
_ -> Doc
"allocatable"
AttrDimension a
_ SrcSpan
_ AList DimensionDeclarator a
dims ->
Doc
"dimension" Doc -> Doc -> Doc
<> Doc -> Doc
parens (FortranVersion -> AList DimensionDeclarator a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v AList DimensionDeclarator a
dims)
AttrExternal a
_ SrcSpan
_ -> Doc
"external"
AttrIntent a
_ SrcSpan
_ Intent
intent ->
Doc
"intent" Doc -> Doc -> Doc
<> Doc -> Doc
parens (FortranVersion -> Intent -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Intent
intent)
AttrIntrinsic a
_ SrcSpan
_ -> Doc
"intrinsic"
AttrOptional a
_ SrcSpan
_ -> Doc
"optional"
AttrPointer a
_ SrcSpan
_ -> Doc
"pointer"
AttrSave a
_ SrcSpan
_ -> Doc
"save"
AttrTarget a
_ SrcSpan
_ -> Doc
"target"
| Bool
otherwise = FortranVersion -> String -> FortranVersion -> Doc
forall a. FortranVersion -> String -> FortranVersion -> a
tooOld FortranVersion
v String
"Declaration attribute" FortranVersion
Fortran90
instance Pretty (Suffix a) where
pprint' :: FortranVersion -> Suffix a -> Doc
pprint' FortranVersion
v (SfxBind a
_ SrcSpan
_ Maybe (Expression a)
mexp)
| FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= FortranVersion
Fortran2003 = Doc
"bind" Doc -> Doc -> Doc
<> Doc -> Doc
parens (Doc
"c" Doc -> Doc -> Doc
<> Doc
comma Doc -> Doc -> Doc
<?+> FortranVersion -> Maybe (Expression a) -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Maybe (Expression a)
mexp)
| Bool
otherwise = FortranVersion -> String -> FortranVersion -> Doc
forall a. FortranVersion -> String -> FortranVersion -> a
tooOld FortranVersion
v String
"Bind suffix" FortranVersion
Fortran2003
instance Pretty Intent where
pprint' :: FortranVersion -> Intent -> Doc
pprint' FortranVersion
v Intent
intent
| FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= FortranVersion
Fortran90 =
case Intent
intent of
Intent
In -> Doc
"in"
Intent
Out -> Doc
"out"
Intent
InOut -> Doc
"inout"
| Bool
otherwise = FortranVersion -> String -> FortranVersion -> Doc
forall a. FortranVersion -> String -> FortranVersion -> a
tooOld FortranVersion
v String
"Declaration attribute" FortranVersion
Fortran90
instance Pretty (FormatItem a) where
pprint' :: FortranVersion -> FormatItem a -> Doc
pprint' FortranVersion
_ (FIHollerith a
_ SrcSpan
_ (ValHollerith String
s)) =
String -> Doc
text (Int -> String
forall a. Show a => a -> String
show (Int -> String) -> Int -> String
forall a b. (a -> b) -> a -> b
$ String -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length String
s) Doc -> Doc -> Doc
<> Char -> Doc
char Char
'h' Doc -> Doc -> Doc
<> String -> Doc
text String
s
pprint' FortranVersion
_ FormatItem a
_ = String -> Doc
forall a. HasCallStack => String -> a
error String
"Not yet supported."
instance Pretty (FlushSpec a) where
pprint' :: FortranVersion -> FlushSpec a -> Doc
pprint' FortranVersion
v (FSUnit a
_ SrcSpan
_ Expression a
e) = Doc
"unit=" Doc -> Doc -> Doc
<> FortranVersion -> Expression a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Expression a
e
pprint' FortranVersion
v (FSIOStat a
_ SrcSpan
_ Expression a
e) = Doc
"iostat=" Doc -> Doc -> Doc
<> FortranVersion -> Expression a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Expression a
e
pprint' FortranVersion
v (FSIOMsg a
_ SrcSpan
_ Expression a
e) = Doc
"iomsg=" Doc -> Doc -> Doc
<> FortranVersion -> Expression a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Expression a
e
pprint' FortranVersion
v (FSErr a
_ SrcSpan
_ Expression a
e) = Doc
"err=" Doc -> Doc -> Doc
<> FortranVersion -> Expression a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Expression a
e
instance Pretty (DoSpecification a) where
pprint' :: FortranVersion -> DoSpecification a -> Doc
pprint' FortranVersion
v (DoSpecification a
_ SrcSpan
_ s :: Statement a
s@StExpressionAssign{} Expression a
limit Maybe (Expression a)
mStride) =
FortranVersion -> Statement a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Statement a
s Doc -> Doc -> Doc
<> Doc
comma
Doc -> Doc -> Doc
<+> FortranVersion -> Expression a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Expression a
limit
Doc -> Doc -> Doc
<> Doc
comma Doc -> Doc -> Doc
<?+> FortranVersion -> Maybe (Expression a) -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Maybe (Expression a)
mStride
pprint' FortranVersion
_ DoSpecification a
_ = String -> Doc
forall a. HasCallStack => String -> a
error String
"Incorrect initialisation in DO specification."
instance Pretty (ControlPair a) where
pprint' :: FortranVersion -> ControlPair a -> Doc
pprint' FortranVersion
v (ControlPair a
_ SrcSpan
_ Maybe String
mStr Expression a
exp)
| FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= FortranVersion
Fortran77
, Just String
str <- Maybe String
mStr = String -> Doc
text String
str Doc -> Doc -> Doc
<> Char -> Doc
char Char
'=' Doc -> Doc -> Doc
<> FortranVersion -> Expression a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Expression a
exp
| FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
< FortranVersion
Fortran77
, Just String
_ <- Maybe String
mStr = FortranVersion -> String -> FortranVersion -> Doc
forall a. FortranVersion -> String -> FortranVersion -> a
tooOld FortranVersion
v String
"Named control pair" FortranVersion
Fortran77
| Bool
otherwise = FortranVersion -> Expression a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Expression a
exp
instance Pretty (AllocOpt a) where
pprint' :: FortranVersion -> AllocOpt a -> Doc
pprint' FortranVersion
v (AOStat a
_ SrcSpan
_ Expression a
e) = Doc
"stat=" Doc -> Doc -> Doc
<> FortranVersion -> Expression a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Expression a
e
pprint' FortranVersion
v (AOErrMsg a
_ SrcSpan
_ Expression a
e)
| FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= FortranVersion
Fortran2003 = Doc
"errmsg=" Doc -> Doc -> Doc
<> FortranVersion -> Expression a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Expression a
e
| Bool
otherwise = FortranVersion -> String -> FortranVersion -> Doc
forall a. FortranVersion -> String -> FortranVersion -> a
tooOld FortranVersion
v String
"Allocate errmsg" FortranVersion
Fortran2003
pprint' FortranVersion
v (AOSource a
_ SrcSpan
_ Expression a
e)
| FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= FortranVersion
Fortran2003 = Doc
"source=" Doc -> Doc -> Doc
<> FortranVersion -> Expression a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Expression a
e
| Bool
otherwise = FortranVersion -> String -> FortranVersion -> Doc
forall a. FortranVersion -> String -> FortranVersion -> a
tooOld FortranVersion
v String
"Allocate source" FortranVersion
Fortran2003
instance Pretty (ImpList a) where
pprint' :: FortranVersion -> ImpList a -> Doc
pprint' FortranVersion
v (ImpList a
_ SrcSpan
_ TypeSpec a
bt AList ImpElement a
els) = FortranVersion -> TypeSpec a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v TypeSpec a
bt Doc -> Doc -> Doc
<+> Doc -> Doc
parens (FortranVersion -> AList ImpElement a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v AList ImpElement a
els)
instance Pretty (CommonGroup a) where
pprint' :: FortranVersion -> CommonGroup a -> Doc
pprint' FortranVersion
v (CommonGroup a
_ SrcSpan
_ Maybe (Expression a)
mName AList Expression a
elems) =
Char -> Doc
char Char
'/' Doc -> Doc -> Doc
<> FortranVersion -> Maybe (Expression a) -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Maybe (Expression a)
mName Doc -> Doc -> Doc
<> Char -> Doc
char Char
'/' Doc -> Doc -> Doc
<> FortranVersion -> AList Expression a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v AList Expression a
elems
instance Pretty (Namelist a) where
pprint' :: FortranVersion -> Namelist a -> Doc
pprint' FortranVersion
Fortran90 (Namelist a
_ SrcSpan
_ Expression a
name AList Expression a
elems) =
Char -> Doc
char Char
'/' Doc -> Doc -> Doc
<> FortranVersion -> Expression a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
Fortran90 Expression a
name Doc -> Doc -> Doc
<> Char -> Doc
char Char
'/' Doc -> Doc -> Doc
<> FortranVersion -> AList Expression a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
Fortran90 AList Expression a
elems
pprint' FortranVersion
v Namelist a
_ = FortranVersion -> String -> FortranVersion -> Doc
forall a. FortranVersion -> String -> FortranVersion -> a
tooOld FortranVersion
v String
"Namelist statement" FortranVersion
Fortran90
instance Pretty (DataGroup a) where
pprint' :: FortranVersion -> DataGroup a -> Doc
pprint' FortranVersion
v (DataGroup a
_ SrcSpan
_ AList Expression a
vars AList Expression a
exps) =
FortranVersion -> AList Expression a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v AList Expression a
vars Doc -> Doc -> Doc
<> Char -> Doc
char Char
'/' Doc -> Doc -> Doc
<> FortranVersion -> AList Expression a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v AList Expression a
exps Doc -> Doc -> Doc
<> Char -> Doc
char Char
'/'
instance Pretty (ImpElement a) where
pprint' :: FortranVersion -> ImpElement a -> Doc
pprint' FortranVersion
_ (ImpCharacter a
_ SrcSpan
_ String
c) = String -> Doc
text String
c
pprint' FortranVersion
_ (ImpRange a
_ SrcSpan
_ String
beg String
end) = String -> Doc
text String
beg Doc -> Doc -> Doc
<> Doc
"-" Doc -> Doc -> Doc
<> String -> Doc
text String
end
instance Pretty (Expression a) where
pprint' :: FortranVersion -> Expression a -> Doc
pprint' FortranVersion
v (ExpValue a
_ SrcSpan
_ Value a
val) =
FortranVersion -> Value a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Value a
val
pprint' FortranVersion
v (ExpBinary a
_ SrcSpan
_ BinaryOp
op Expression a
e1 Expression a
e2) =
Doc -> Doc
parens (FortranVersion -> Expression a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Expression a
e1 Doc -> Doc -> Doc
<+> FortranVersion -> BinaryOp -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v BinaryOp
op Doc -> Doc -> Doc
<+> FortranVersion -> Expression a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Expression a
e2)
pprint' FortranVersion
v (ExpUnary a
_ SrcSpan
_ UnaryOp
op Expression a
e) =
FortranVersion -> UnaryOp -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v UnaryOp
op Doc -> Doc -> Doc
<+> FortranVersion -> Expression a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Expression a
e
pprint' FortranVersion
v (ExpSubscript a
_ SrcSpan
_ Expression a
e AList Index a
ixs) =
FortranVersion -> Expression a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Expression a
e Doc -> Doc -> Doc
<> Doc -> Doc
parens (FortranVersion -> AList Index a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v AList Index a
ixs)
pprint' FortranVersion
v (ExpDataRef a
_ SrcSpan
_ Expression a
e1 Expression a
e2) =
FortranVersion -> Expression a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Expression a
e1 Doc -> Doc -> Doc
<+> Char -> Doc
char Char
'%' Doc -> Doc -> Doc
<+> FortranVersion -> Expression a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Expression a
e2
pprint' FortranVersion
v (ExpFunctionCall a
_ SrcSpan
_ Expression a
e Maybe (AList Argument a)
mes) =
FortranVersion -> Expression a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Expression a
e Doc -> Doc -> Doc
<> Doc -> Doc
parens (FortranVersion -> Maybe (AList Argument a) -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Maybe (AList Argument a)
mes)
pprint' FortranVersion
v (ExpImpliedDo a
_ SrcSpan
_ AList Expression a
es DoSpecification a
dospec) =
FortranVersion -> AList Expression a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v AList Expression a
es Doc -> Doc -> Doc
<> Doc
comma Doc -> Doc -> Doc
<+> FortranVersion -> DoSpecification a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v DoSpecification a
dospec
pprint' FortranVersion
v (ExpInitialisation a
_ SrcSpan
_ AList Expression a
es) =
Doc
"(/" Doc -> Doc -> Doc
<> FortranVersion -> AList Expression a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v AList Expression a
es Doc -> Doc -> Doc
<> Doc
"/)"
pprint' FortranVersion
v (ExpReturnSpec a
_ SrcSpan
_ Expression a
e) =
Char -> Doc
char Char
'*' Doc -> Doc -> Doc
<> FortranVersion -> Expression a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Expression a
e
instance Pretty (Index a) where
pprint' :: FortranVersion -> Index a -> Doc
pprint' FortranVersion
v (IxSingle a
_ SrcSpan
_ Maybe String
Nothing Expression a
e) = FortranVersion -> Expression a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Expression a
e
pprint' FortranVersion
v (IxSingle a
_ SrcSpan
_ (Just String
_) Expression a
e) = FortranVersion -> Expression a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Expression a
e
pprint' FortranVersion
v (IxRange a
_ SrcSpan
_ Maybe (Expression a)
low Maybe (Expression a)
up Maybe (Expression a)
stride) =
FortranVersion -> Maybe (Expression a) -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Maybe (Expression a)
low Doc -> Doc -> Doc
<> Doc
colon Doc -> Doc -> Doc
<> FortranVersion -> Maybe (Expression a) -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Maybe (Expression a)
up Doc -> Doc -> Doc
<> Doc
colon Doc -> Doc -> Doc
<?> FortranVersion -> Maybe (Expression a) -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Maybe (Expression a)
stride
instance FirstParameter (Value a) String
instance Pretty (Value a) where
pprint' :: FortranVersion -> Value a -> Doc
pprint' FortranVersion
_ Value a
ValStar = Char -> Doc
char Char
'*'
pprint' FortranVersion
_ Value a
ValColon = Char -> Doc
char Char
':'
pprint' FortranVersion
v Value a
ValAssignment
| FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= FortranVersion
Fortran90 = Doc
"assignment (=)"
| Bool
otherwise = FortranVersion -> String -> FortranVersion -> Doc
forall a. FortranVersion -> String -> FortranVersion -> a
tooOld FortranVersion
v String
"Assignment" FortranVersion
Fortran90
pprint' FortranVersion
v (ValOperator String
op)
| FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= FortranVersion
Fortran90 = Doc
"operator" Doc -> Doc -> Doc
<+> Doc -> Doc
parens (String -> Doc
text String
op)
| Bool
otherwise = FortranVersion -> String -> FortranVersion -> Doc
forall a. FortranVersion -> String -> FortranVersion -> a
tooOld FortranVersion
v String
"Operator" FortranVersion
Fortran90
pprint' FortranVersion
v (ValComplex Expression a
e1 Expression a
e2) = Doc -> Doc
parens (Doc -> Doc) -> Doc -> Doc
forall a b. (a -> b) -> a -> b
$ [Doc] -> Doc
commaSep [FortranVersion -> Expression a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Expression a
e1, FortranVersion -> Expression a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Expression a
e2]
pprint' FortranVersion
_ (ValString String
str) = Doc -> Doc
quotes (Doc -> Doc) -> Doc -> Doc
forall a b. (a -> b) -> a -> b
$ String -> Doc
text String
str
pprint' FortranVersion
_ Value a
valLit = String -> Doc
text (String -> Doc) -> (Value a -> String) -> Value a -> Doc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Value a -> String
forall a e. FirstParameter a e => a -> e
getFirstParameter (Value a -> Doc) -> Value a -> Doc
forall a b. (a -> b) -> a -> b
$ Value a
valLit
instance IndentablePretty (StructureItem a) where
pprint :: FortranVersion -> StructureItem a -> Indentation -> Doc
pprint FortranVersion
v (StructFields a
a SrcSpan
s TypeSpec a
spec Maybe (AList Attribute a)
mAttrs AList Declarator a
decls) Indentation
_ = FortranVersion -> Statement a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v (a
-> SrcSpan
-> TypeSpec a
-> Maybe (AList Attribute a)
-> AList Declarator a
-> Statement a
forall a.
a
-> SrcSpan
-> TypeSpec a
-> Maybe (AList Attribute a)
-> AList Declarator a
-> Statement a
StDeclaration a
a SrcSpan
s TypeSpec a
spec Maybe (AList Attribute a)
mAttrs AList Declarator a
decls)
pprint FortranVersion
v (StructUnion a
_ SrcSpan
_ AList UnionMap a
maps) Indentation
i =
Doc
"union" Doc -> Doc -> Doc
<> Doc
newline Doc -> Doc -> Doc
<>
(Doc -> UnionMap a -> Doc) -> Doc -> [UnionMap a] -> Doc
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' (\Doc
doc UnionMap a
item -> Doc
doc Doc -> Doc -> Doc
<> FortranVersion -> UnionMap a -> Indentation -> Doc
forall t.
IndentablePretty t =>
FortranVersion -> t -> Indentation -> Doc
pprint FortranVersion
v UnionMap a
item (Indentation -> Indentation
incIndentation Indentation
i) Doc -> Doc -> Doc
<> Doc
newline) Doc
empty (AList UnionMap a -> [UnionMap a]
forall (t :: * -> *) a. AList t a -> [t a]
aStrip AList UnionMap a
maps) Doc -> Doc -> Doc
<>
Doc
"end union"
pprint FortranVersion
v (StructStructure a
a SrcSpan
s Maybe String
mName String
_ AList StructureItem a
items) Indentation
_ = FortranVersion -> Statement a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v (a
-> SrcSpan -> Maybe String -> AList StructureItem a -> Statement a
forall a.
a
-> SrcSpan -> Maybe String -> AList StructureItem a -> Statement a
StStructure a
a SrcSpan
s Maybe String
mName AList StructureItem a
items)
instance IndentablePretty (UnionMap a) where
pprint :: FortranVersion -> UnionMap a -> Indentation -> Doc
pprint FortranVersion
v (UnionMap a
_ SrcSpan
_ AList StructureItem a
items) Indentation
i =
Doc
"map" Doc -> Doc -> Doc
<> Doc
newline Doc -> Doc -> Doc
<>
(Doc -> StructureItem a -> Doc) -> Doc -> [StructureItem a] -> Doc
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' (\Doc
doc StructureItem a
item -> Doc
doc Doc -> Doc -> Doc
<> FortranVersion -> StructureItem a -> Indentation -> Doc
forall t.
IndentablePretty t =>
FortranVersion -> t -> Indentation -> Doc
pprint FortranVersion
v StructureItem a
item (Indentation -> Indentation
incIndentation Indentation
i) Doc -> Doc -> Doc
<> Doc
newline) Doc
empty (AList StructureItem a -> [StructureItem a]
forall (t :: * -> *) a. AList t a -> [t a]
aStrip AList StructureItem a
items) Doc -> Doc -> Doc
<>
Doc
"end map"
instance Pretty (Declarator a) where
pprint' :: FortranVersion -> Declarator a -> Doc
pprint' FortranVersion
v (DeclVariable a
_ SrcSpan
_ Expression a
e Maybe (Expression a)
mLen Maybe (Expression a)
mInit)
| FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= FortranVersion
Fortran90 =
FortranVersion -> Expression a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Expression a
e Doc -> Doc -> Doc
<>
Char -> Doc
char Char
'*' Doc -> Doc -> Doc
<?> FortranVersion -> Maybe (Expression a) -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Maybe (Expression a)
mLen Doc -> Doc -> Doc
<+>
Char -> Doc
char Char
'=' Doc -> Doc -> Doc
<?+> FortranVersion -> Maybe (Expression a) -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Maybe (Expression a)
mInit
pprint' FortranVersion
v (DeclVariable a
_ SrcSpan
_ Expression a
e Maybe (Expression a)
mLen Maybe (Expression a)
mInit)
| FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= FortranVersion
Fortran77 =
case Maybe (Expression a)
mInit of
Maybe (Expression a)
Nothing -> FortranVersion -> Expression a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Expression a
e Doc -> Doc -> Doc
<>
Char -> Doc
char Char
'*' Doc -> Doc -> Doc
<?> FortranVersion -> Maybe (Expression a) -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Maybe (Expression a)
mLen
Just Expression a
initial -> FortranVersion -> Expression a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Expression a
e Doc -> Doc -> Doc
<>
Char -> Doc
char Char
'*' Doc -> Doc -> Doc
<?> FortranVersion -> Maybe (Expression a) -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Maybe (Expression a)
mLen Doc -> Doc -> Doc
<>
Char -> Doc
char Char
'/' Doc -> Doc -> Doc
<> FortranVersion -> Expression a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Expression a
initial Doc -> Doc -> Doc
<> Char -> Doc
char Char
'/'
pprint' FortranVersion
v (DeclVariable a
_ SrcSpan
_ Expression a
e Maybe (Expression a)
mLen Maybe (Expression a)
mInit)
| Maybe (Expression a)
Nothing <- Maybe (Expression a)
mLen
, Maybe (Expression a)
Nothing <- Maybe (Expression a)
mInit = FortranVersion -> Expression a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Expression a
e
| Just Expression a
_ <- Maybe (Expression a)
mInit = FortranVersion -> String -> FortranVersion -> Doc
forall a. FortranVersion -> String -> FortranVersion -> a
tooOld FortranVersion
v String
"Variable initialisation" FortranVersion
Fortran90
| Just Expression a
_ <- Maybe (Expression a)
mLen = FortranVersion -> String -> FortranVersion -> Doc
forall a. FortranVersion -> String -> FortranVersion -> a
tooOld FortranVersion
v String
"Variable width" FortranVersion
Fortran77
pprint' FortranVersion
v (DeclArray a
_ SrcSpan
_ Expression a
e AList DimensionDeclarator a
dims Maybe (Expression a)
mLen Maybe (Expression a)
mInit)
| FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= FortranVersion
Fortran90 =
FortranVersion -> Expression a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Expression a
e Doc -> Doc -> Doc
<> Doc -> Doc
parens (FortranVersion -> AList DimensionDeclarator a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v AList DimensionDeclarator a
dims) Doc -> Doc -> Doc
<+>
Doc
"*" Doc -> Doc -> Doc
<?> FortranVersion -> Maybe (Expression a) -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Maybe (Expression a)
mLen Doc -> Doc -> Doc
<+>
Doc
equals Doc -> Doc -> Doc
<?> FortranVersion -> Maybe (Expression a) -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Maybe (Expression a)
mInit
pprint' FortranVersion
v (DeclArray a
_ SrcSpan
_ Expression a
e AList DimensionDeclarator a
dims Maybe (Expression a)
mLen Maybe (Expression a)
mInit)
| FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= FortranVersion
Fortran77 =
case Maybe (Expression a)
mInit of
Maybe (Expression a)
Nothing -> FortranVersion -> Expression a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Expression a
e Doc -> Doc -> Doc
<> Doc -> Doc
parens (FortranVersion -> AList DimensionDeclarator a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v AList DimensionDeclarator a
dims) Doc -> Doc -> Doc
<>
Doc
"*" Doc -> Doc -> Doc
<?> FortranVersion -> Maybe (Expression a) -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Maybe (Expression a)
mLen
Just Expression a
initial ->
let initDoc :: Doc
initDoc = case Expression a
initial of
ExpInitialisation a
_ SrcSpan
_ AList Expression a
es ->
Char -> Doc
char Char
'/' Doc -> Doc -> Doc
<> FortranVersion -> AList Expression a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v AList Expression a
es Doc -> Doc -> Doc
<> Char -> Doc
char Char
'/'
Expression a
e' -> FortranVersion -> Expression a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Expression a
e'
in FortranVersion -> Expression a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Expression a
e Doc -> Doc -> Doc
<> Doc -> Doc
parens (FortranVersion -> AList DimensionDeclarator a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v AList DimensionDeclarator a
dims) Doc -> Doc -> Doc
<>
Doc
"*" Doc -> Doc -> Doc
<?> FortranVersion -> Maybe (Expression a) -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Maybe (Expression a)
mLen Doc -> Doc -> Doc
<> Doc
initDoc
pprint' FortranVersion
v (DeclArray a
_ SrcSpan
_ Expression a
e AList DimensionDeclarator a
dims Maybe (Expression a)
mLen Maybe (Expression a)
mInit)
| Maybe (Expression a)
Nothing <- Maybe (Expression a)
mLen
, Maybe (Expression a)
Nothing <- Maybe (Expression a)
mInit = FortranVersion -> Expression a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Expression a
e Doc -> Doc -> Doc
<> Doc -> Doc
parens (FortranVersion -> AList DimensionDeclarator a -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v AList DimensionDeclarator a
dims)
| Just Expression a
_ <- Maybe (Expression a)
mInit = FortranVersion -> String -> FortranVersion -> Doc
forall a. FortranVersion -> String -> FortranVersion -> a
tooOld FortranVersion
v String
"Variable initialisation" FortranVersion
Fortran90
| Just Expression a
_ <- Maybe (Expression a)
mLen = FortranVersion -> String -> FortranVersion -> Doc
forall a. FortranVersion -> String -> FortranVersion -> a
tooOld FortranVersion
v String
"Variable width" FortranVersion
Fortran77
instance Pretty (DimensionDeclarator a) where
pprint' :: FortranVersion -> DimensionDeclarator a -> Doc
pprint' FortranVersion
v (DimensionDeclarator a
_ SrcSpan
_ Maybe (Expression a)
me1 Maybe (Expression a)
me2) =
FortranVersion -> Maybe (Expression a) -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Maybe (Expression a)
me1 Doc -> Doc -> Doc
<?> Doc
colon Doc -> Doc -> Doc
<> FortranVersion -> Maybe (Expression a) -> Doc
forall t. Pretty t => FortranVersion -> t -> Doc
pprint' FortranVersion
v Maybe (Expression a)
me2
instance Pretty UnaryOp where
pprint' :: FortranVersion -> UnaryOp -> Doc
pprint' FortranVersion
_ UnaryOp
Plus = Char -> Doc
char Char
'+'
pprint' FortranVersion
_ UnaryOp
Minus = Char -> Doc
char Char
'-'
pprint' FortranVersion
_ UnaryOp
Not = Doc
".not."
pprint' FortranVersion
v (UnCustom String
custom)
| FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= FortranVersion
Fortran90 = String -> Doc
text (String -> Doc) -> String -> Doc
forall a b. (a -> b) -> a -> b
$ String
"." String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
custom String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"."
| Bool
otherwise = FortranVersion -> String -> FortranVersion -> Doc
forall a. FortranVersion -> String -> FortranVersion -> a
tooOld FortranVersion
v String
"Custom unary operator" FortranVersion
Fortran90
instance Pretty BinaryOp where
pprint' :: FortranVersion -> BinaryOp -> Doc
pprint' FortranVersion
_ BinaryOp
Addition = Char -> Doc
char Char
'+'
pprint' FortranVersion
_ BinaryOp
Subtraction = Char -> Doc
char Char
'-'
pprint' FortranVersion
_ BinaryOp
Multiplication = Char -> Doc
char Char
'*'
pprint' FortranVersion
_ BinaryOp
Division = Char -> Doc
char Char
'/'
pprint' FortranVersion
_ BinaryOp
Exponentiation = Doc
"**"
pprint' FortranVersion
v BinaryOp
Concatenation
| FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= FortranVersion
Fortran77 = Doc
"//"
| Bool
otherwise = FortranVersion -> String -> FortranVersion -> Doc
forall a. FortranVersion -> String -> FortranVersion -> a
tooOld FortranVersion
v String
"Character type" FortranVersion
Fortran77
pprint' FortranVersion
v BinaryOp
GT = if FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
<= FortranVersion
Fortran77Extended then Doc
".gt." else Doc
">"
pprint' FortranVersion
v BinaryOp
LT = if FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
<= FortranVersion
Fortran77Extended then Doc
".lt." else Doc
"<"
pprint' FortranVersion
v BinaryOp
LTE = if FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
<= FortranVersion
Fortran77Extended then Doc
".le." else Doc
"<="
pprint' FortranVersion
v BinaryOp
GTE = if FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
<= FortranVersion
Fortran77Extended then Doc
".ge." else Doc
">="
pprint' FortranVersion
v BinaryOp
EQ = if FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
<= FortranVersion
Fortran77Extended then Doc
".eq." else Doc
"=="
pprint' FortranVersion
v BinaryOp
NE = if FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
<= FortranVersion
Fortran77Extended then Doc
".ne." else Doc
"/="
pprint' FortranVersion
_ BinaryOp
Or = Doc
".or."
pprint' FortranVersion
_ BinaryOp
XOr = Doc
".xor."
pprint' FortranVersion
_ BinaryOp
And = Doc
".and."
pprint' FortranVersion
v BinaryOp
Equivalent
| FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= FortranVersion
Fortran77 = Doc
".eqv."
| Bool
otherwise = FortranVersion -> String -> FortranVersion -> Doc
forall a. FortranVersion -> String -> FortranVersion -> a
tooOld FortranVersion
v String
".EQV. operator" FortranVersion
Fortran77
pprint' FortranVersion
v BinaryOp
NotEquivalent
| FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= FortranVersion
Fortran77 = Doc
".neqv."
| Bool
otherwise = FortranVersion -> String -> FortranVersion -> Doc
forall a. FortranVersion -> String -> FortranVersion -> a
tooOld FortranVersion
v String
".NEQV. operator" FortranVersion
Fortran77
pprint' FortranVersion
v (BinCustom String
custom)
| FortranVersion
v FortranVersion -> FortranVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= FortranVersion
Fortran90 = String -> Doc
text String
custom
| Bool
otherwise = FortranVersion -> String -> FortranVersion -> Doc
forall a. FortranVersion -> String -> FortranVersion -> a
tooOld FortranVersion
v String
"Custom binary operator" FortranVersion
Fortran90
commaSep :: [Doc] -> Doc
commaSep :: [Doc] -> Doc
commaSep = [Doc] -> Doc
hcat ([Doc] -> Doc) -> ([Doc] -> [Doc]) -> [Doc] -> Doc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Doc -> [Doc] -> [Doc]
punctuate Doc
", "
data ReformatState
= RefmtStNewline Int
|
| RefmtStStmt Int
deriving (ReformatState -> ReformatState -> Bool
(ReformatState -> ReformatState -> Bool)
-> (ReformatState -> ReformatState -> Bool) -> Eq ReformatState
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ReformatState -> ReformatState -> Bool
$c/= :: ReformatState -> ReformatState -> Bool
== :: ReformatState -> ReformatState -> Bool
$c== :: ReformatState -> ReformatState -> Bool
Eq, Eq ReformatState
Eq ReformatState
-> (ReformatState -> ReformatState -> Ordering)
-> (ReformatState -> ReformatState -> Bool)
-> (ReformatState -> ReformatState -> Bool)
-> (ReformatState -> ReformatState -> Bool)
-> (ReformatState -> ReformatState -> Bool)
-> (ReformatState -> ReformatState -> ReformatState)
-> (ReformatState -> ReformatState -> ReformatState)
-> Ord ReformatState
ReformatState -> ReformatState -> Bool
ReformatState -> ReformatState -> Ordering
ReformatState -> ReformatState -> ReformatState
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ReformatState -> ReformatState -> ReformatState
$cmin :: ReformatState -> ReformatState -> ReformatState
max :: ReformatState -> ReformatState -> ReformatState
$cmax :: ReformatState -> ReformatState -> ReformatState
>= :: ReformatState -> ReformatState -> Bool
$c>= :: ReformatState -> ReformatState -> Bool
> :: ReformatState -> ReformatState -> Bool
$c> :: ReformatState -> ReformatState -> Bool
<= :: ReformatState -> ReformatState -> Bool
$c<= :: ReformatState -> ReformatState -> Bool
< :: ReformatState -> ReformatState -> Bool
$c< :: ReformatState -> ReformatState -> Bool
compare :: ReformatState -> ReformatState -> Ordering
$ccompare :: ReformatState -> ReformatState -> Ordering
$cp1Ord :: Eq ReformatState
Ord, Int -> ReformatState -> String -> String
[ReformatState] -> String -> String
ReformatState -> String
(Int -> ReformatState -> String -> String)
-> (ReformatState -> String)
-> ([ReformatState] -> String -> String)
-> Show ReformatState
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [ReformatState] -> String -> String
$cshowList :: [ReformatState] -> String -> String
show :: ReformatState -> String
$cshow :: ReformatState -> String
showsPrec :: Int -> ReformatState -> String -> String
$cshowsPrec :: Int -> ReformatState -> String -> String
Show)
reformatMixedFormInsertContinuations :: String -> String
reformatMixedFormInsertContinuations :: String -> String
reformatMixedFormInsertContinuations = ReformatState -> String -> String
go ReformatState
stNewline
where
go :: ReformatState -> String -> String
go :: ReformatState -> String -> String
go ReformatState
_ [] = []
go ReformatState
_ (Char
'\n':String
xs) = Char
'\n' Char -> String -> String
forall a. a -> [a] -> [a]
: ReformatState -> String -> String
go ReformatState
stNewline String
xs
go ReformatState
RefmtStComment (Char
x:String
xs) = Char
x Char -> String -> String
forall a. a -> [a] -> [a]
: ReformatState -> String -> String
go ReformatState
RefmtStComment String
xs
go (RefmtStNewline Int
0) (Char
'c':String
xs) = Char
'c' Char -> String -> String
forall a. a -> [a] -> [a]
: ReformatState -> String -> String
go ReformatState
RefmtStComment String
xs
go (RefmtStNewline Int
col) (Char
x:String
xs) =
case Char
x of
Char
' ' -> Char
' ' Char -> String -> String
forall a. a -> [a] -> [a]
: ReformatState -> String -> String
go (Int -> ReformatState
RefmtStNewline (Int
colInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1)) String
xs
Char
'!' -> Char
'!' Char -> String -> String
forall a. a -> [a] -> [a]
: ReformatState -> String -> String
go ReformatState
RefmtStComment String
xs
Char
_ -> Char
x Char -> String -> String
forall a. a -> [a] -> [a]
: ReformatState -> String -> String
go (Int -> ReformatState
RefmtStStmt (Int
colInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1)) String
xs
go (RefmtStStmt Int
col) (Char
x:String
xs)
| Int
col Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
maxCol =
case String
xs of
[] -> Char
x Char -> String -> String
forall a. a -> [a] -> [a]
: ReformatState -> String -> String
go (Int -> ReformatState
RefmtStStmt (Int
colInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1)) String
xs
Char
x':String
_ ->
case Char
x' of
Char
'\n' -> Char
x Char -> String -> String
forall a. a -> [a] -> [a]
: ReformatState -> String -> String
go (Int -> ReformatState
RefmtStStmt (Int
colInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1)) String
xs
Char
_ ->
Char
'&' Char -> String -> String
forall a. a -> [a] -> [a]
: ReformatState -> String -> String
go (Int -> ReformatState
RefmtStStmt (Int
colInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1)) (String
"\n &" String -> String -> String
forall a. [a] -> [a] -> [a]
++ Char
xChar -> String -> String
forall a. a -> [a] -> [a]
:String
xs)
| Bool
otherwise = Char
x Char -> String -> String
forall a. a -> [a] -> [a]
: ReformatState -> String -> String
go (Int -> ReformatState
RefmtStStmt (Int
colInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1)) String
xs
maxCol :: Int
maxCol = Int
72
stNewline :: ReformatState
stNewline = Int -> ReformatState
RefmtStNewline Int
0