Skip to content

Commit 606048d

Browse files
committed
add associate block tests
1 parent 15b8d06 commit 606048d

File tree

4 files changed

+84
-22
lines changed

4 files changed

+84
-22
lines changed

src/Language/Fortran/Parser/Fortran2003.y

Lines changed: 5 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1,8 +1,10 @@
11
-- -*- Mode: Haskell -*-
2+
-- vim: ft=haskell
23
{
34
-- Incomplete work-in-progress.
45
module Language.Fortran.Parser.Fortran2003 ( functionParser
56
, statementParser
7+
, blockParser
68
, fortran2003Parser
79
, fortran2003ParserWithTransforms
810
, fortran2003ParserWithModFiles
@@ -32,9 +34,10 @@ import Debug.Trace
3234

3335
}
3436

35-
%name programParser PROGRAM
37+
%name programParser PROGRAM
38+
%name functionParser SUBPROGRAM_UNIT
39+
%name blockParser BLOCK
3640
%name statementParser STATEMENT
37-
%name functionParser SUBPROGRAM_UNIT
3841
%monad { LexAction }
3942
%lexer { lexer } { TEOF _ }
4043
%tokentype { Token }

src/Language/Fortran/PrettyPrint.hs

Lines changed: 4 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -327,14 +327,16 @@ instance IndentablePretty (Block a) where
327327
then indent i (pprint' v label <+> stDoc)
328328
else pprint' v mLabel `overlay` indent i stDoc
329329

330+
-- Note that binary expressions such as @a*b@ will always be wrapped in
331+
-- brackets. It appears to be built into 'Expression''s 'Pretty' instance.
330332
pprint v (BlAssociate _ _ mLabel mName abbrevs bodies mEndLabel) i
331-
| v >= Fortran90 =
333+
| v >= Fortran2003 =
332334
labeledIndent mLabel
333335
$ pprint' v mName <?> colon
334336
<+> ("associate" <+> "(" <> pprint' v abbrevs <> ")" <> newline)
335337
<> pprint v bodies nextI
336338
<> labeledIndent mEndLabel ("end associate" <+> pprint' v mName <> newline)
337-
| otherwise = tooOld v "Associate block" Fortran90
339+
| otherwise = tooOld v "Associate block" Fortran2003
338340
where
339341
nextI = incIndentation i
340342
labeledIndent label stDoc =
@@ -359,7 +361,6 @@ instance Pretty String where
359361
instance Pretty (e a) => Pretty (AList e a) where
360362
pprint' v es = commaSep (map (pprint' v) (aStrip es))
361363

362-
-- TODO associate
363364
instance (Pretty (t1 a), Pretty (t2 a)) => Pretty (ATuple t1 t2 a) where
364365
pprint' v (ATuple _ _ t1 t2) = pprint' v t1 <+> "=>" <+> pprint' v t2
365366

test/Language/Fortran/Parser/Fortran2003Spec.hs

Lines changed: 38 additions & 17 deletions
Original file line numberDiff line numberDiff line change
@@ -21,13 +21,18 @@ eParser sourceCode =
2121
paddedSourceCode = B.pack $ " a = " ++ sourceCode
2222
parseState = initParseState paddedSourceCode Fortran2003 "<unknown>"
2323

24+
simpleParser :: Parse AlexInput Token a -> String -> a
25+
simpleParser p sourceCode =
26+
evalParse p $ initParseState (B.pack sourceCode) Fortran2003 "<unknown>"
27+
2428
sParser :: String -> Statement ()
25-
sParser sourceCode =
26-
evalParse statementParser $ initParseState (B.pack sourceCode) Fortran2003 "<unknown>"
29+
sParser = simpleParser statementParser
2730

2831
fParser :: String -> ProgramUnit ()
29-
fParser sourceCode =
30-
evalParse functionParser $ initParseState (B.pack sourceCode) Fortran2003 "<unknown>"
32+
fParser = simpleParser functionParser
33+
34+
bParser :: String -> Block ()
35+
bParser = simpleParser blockParser
3136

3237
spec :: Spec
3338
spec =
@@ -141,16 +146,32 @@ spec =
141146
sParser "real, protected, public :: x" `shouldBe'` st1
142147
sParser "protected x" `shouldBe'` st2
143148

144-
describe "labelled where" $ do
145-
it "parses where construct statement" $
146-
sParser "foo: where (.true.)" `shouldBe'` StWhereConstruct () u (Just "foo") valTrue
147-
148-
it "parses elsewhere statement" $
149-
sParser "elsewhere ab101" `shouldBe'` StElsewhere () u (Just "ab101") Nothing
150-
151-
it "parses elsewhere statement" $ do
152-
let exp = ExpBinary () u GT (varGen "a") (varGen "b")
153-
sParser "elsewhere (a > b) A123" `shouldBe'` StElsewhere () u (Just "a123") (Just exp)
154-
155-
it "parses endwhere statement" $
156-
sParser "endwhere foo1" `shouldBe'` StEndWhere () u (Just "foo1")
149+
describe "labelled where" $ do
150+
it "parses where construct statement" $
151+
sParser "foo: where (.true.)" `shouldBe'` StWhereConstruct () u (Just "foo") valTrue
152+
153+
it "parses elsewhere statement" $
154+
sParser "elsewhere ab101" `shouldBe'` StElsewhere () u (Just "ab101") Nothing
155+
156+
it "parses elsewhere statement" $ do
157+
let exp = ExpBinary () u GT (varGen "a") (varGen "b")
158+
sParser "elsewhere (a > b) A123" `shouldBe'` StElsewhere () u (Just "a123") (Just exp)
159+
160+
it "parses endwhere statement" $
161+
sParser "endwhere foo1" `shouldBe'` StEndWhere () u (Just "foo1")
162+
163+
describe "associate block" $ do
164+
it "parses multiple assignment associate block" $ do
165+
let text = unlines [ "associate (x => a, y => (a * b))"
166+
, " print *, x"
167+
, " print *, y"
168+
, "end associate" ]
169+
expected = BlAssociate () u Nothing Nothing abbrevs body' Nothing
170+
body' = [blStmtPrint "x", blStmtPrint "y"]
171+
blStmtPrint x = BlStatement () u Nothing (stmtPrint x)
172+
stmtPrint x = StPrint () u starVal (Just $ AList () u [ varGen x ])
173+
abbrevs = AList () u [abbrev "x" (expValVar "a"), abbrev "y" (expBinVars Multiplication "a" "b")]
174+
abbrev var expr = ATuple () u (expValVar var) expr
175+
expValVar x = ExpValue () u (ValVariable x)
176+
expBinVars op x1 x2 = ExpBinary () u op (expValVar x1) (expValVar x2)
177+
bParser text `shouldBe'` expected

test/Language/Fortran/PrettyPrintSpec.hs

Lines changed: 37 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -404,6 +404,43 @@ spec =
404404
, "42 end select" ]
405405
pprint Fortran90 bl (Just 0) `shouldBe` text expect
406406

407+
describe "Case" $
408+
it "prints multi-case select case construct" $ do
409+
let range = IxRange () u (Just $ intGen 2) (Just $ intGen 4) Nothing
410+
let cases = [ Just (AList () u [range])
411+
, Just (AList () u [ IxSingle () u Nothing (intGen 7) ])
412+
, Nothing ]
413+
let bodies = replicate 3 body
414+
let bl = BlCase () u Nothing Nothing (varGen "x") cases bodies (Just (intGen 42))
415+
let expect = unlines [ "select case (x)"
416+
, " case (2:4)"
417+
, " print *, i"
418+
, " i = (i - 1)"
419+
, " case (7)"
420+
, " print *, i"
421+
, " i = (i - 1)"
422+
, " case default"
423+
, " print *, i"
424+
, " i = (i - 1)"
425+
, "42 end select" ]
426+
pprint Fortran90 bl (Just 0) `shouldBe` text expect
427+
428+
describe "Associate" $
429+
it "prints multi-abbreviation associate block (Fortran2003)" $ do
430+
let bl = BlAssociate () u Nothing Nothing abbrevs body' Nothing
431+
body' = [blStmtPrint "x", blStmtPrint "y"]
432+
blStmtPrint x = BlStatement () u Nothing (stmtPrint x)
433+
stmtPrint x = StPrint () u starVal (Just $ AList () u [ varGen x ])
434+
abbrevs = AList () u [abbrev "x" (expValVar "a"), abbrev "y" (expBinVars Multiplication "a" "b")]
435+
abbrev var expr = ATuple () u (expValVar var) expr
436+
expValVar x = ExpValue () u (ValVariable x)
437+
expBinVars op x1 x2 = ExpBinary () u op (expValVar x1) (expValVar x2)
438+
let expect = unlines [ "associate (x => a, y => (a * b))"
439+
, " print *, x"
440+
, " print *, y"
441+
, "end associate" ]
442+
pprint Fortran2003 bl (Just 0) `shouldBe` text expect
443+
407444
describe "Program units" $ do
408445
describe "Main" $ do
409446
it "prints 90 style main without sub programs" $ do

0 commit comments

Comments
 (0)