Skip to content

Commit 0198f73

Browse files
authored
Merge pull request #152 from andreasabel/issue71
Fixed crash in issue 71
2 parents 5bbb6fb + 58ea5ad commit 0198f73

File tree

4 files changed

+80
-11
lines changed

4 files changed

+80
-11
lines changed

alex.cabal

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -109,6 +109,7 @@ extra-source-files:
109109
tests/posn_typeclass_bytestring.x
110110
tests/strict_typeclass.x
111111
tests/unicode.x
112+
tests/issue_71.x
112113

113114
source-repository head
114115
type: git

src/DFAMin.hs

Lines changed: 29 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,9 @@
11
{-# OPTIONS_GHC -fno-warn-name-shadowing #-}
2-
{-# LANGUAGE PatternGuards #-}
2+
3+
{-# LANGUAGE PatternGuards #-}
4+
{-# LANGUAGE ScopedTypeVariables #-}
5+
{-# LANGUAGE TupleSections #-}
6+
37
module DFAMin (minimizeDFA) where
48

59
import AbsSyn
@@ -10,7 +14,7 @@ import Data.IntSet (IntSet)
1014
import qualified Data.IntSet as IS
1115
import Data.IntMap (IntMap)
1216
import qualified Data.IntMap as IM
13-
import Data.List as List
17+
import qualified Data.List as List
1418

1519

1620
-- Hopcroft's Algorithm for DFA minimization (cut/pasted from Wikipedia):
@@ -31,28 +35,32 @@ import Data.List as List
3135
-- end;
3236
-- end;
3337

34-
minimizeDFA :: Ord a => DFA Int a -> DFA Int a
38+
minimizeDFA :: forall a. Ord a => DFA Int a -> DFA Int a
3539
minimizeDFA dfa@DFA { dfa_start_states = starts,
3640
dfa_states = statemap
3741
}
3842
= DFA { dfa_start_states = starts,
3943
dfa_states = Map.fromList states }
4044
where
45+
equiv_classes :: [EquivalenceClass]
4146
equiv_classes = groupEquivStates dfa
4247

48+
numbered_states :: [(Int, EquivalenceClass)]
4349
numbered_states = number (length starts) equiv_classes
4450

4551
-- assign each state in the minimized DFA a number, making
4652
-- sure that we assign the numbers [0..] to the start states.
53+
number :: Int -> [EquivalenceClass] -> [(Int, EquivalenceClass)]
4754
number _ [] = []
4855
number n (ss:sss) =
4956
case filter (`IS.member` ss) starts of
5057
[] -> (n,ss) : number (n+1) sss
51-
starts' -> zip starts' (repeat ss) ++ number n sss
58+
starts' -> map (,ss) starts' ++ number n sss
5259
-- if one of the states of the minimized DFA corresponds
5360
-- to multiple starts states, we just have to duplicate
5461
-- that state.
5562

63+
states :: [(Int, State Int a)]
5664
states = [
5765
let old_states = map (lookup statemap) (IS.toList equiv)
5866
accs = map fix_acc (state_acc (head old_states))
@@ -64,38 +72,50 @@ minimizeDFA dfa@DFA { dfa_start_states = starts,
6472
| (n, equiv) <- numbered_states
6573
]
6674

75+
fix_acc :: Accept a -> Accept a
6776
fix_acc acc = acc { accRightCtx = fix_rctxt (accRightCtx acc) }
6877

78+
fix_rctxt :: RightContext SNum -> RightContext SNum
6979
fix_rctxt (RightContextRExp s) = RightContextRExp (get_new s)
7080
fix_rctxt other = other
7181

82+
lookup :: Ord k => Map k v -> k -> v
7283
lookup m k = Map.findWithDefault (error "minimizeDFA") k m
84+
85+
get_new :: Int -> Int
7386
get_new = lookup old_to_new
7487

7588
old_to_new :: Map Int Int
7689
old_to_new = Map.fromList [ (s,n) | (n,ss) <- numbered_states,
7790
s <- IS.toList ss ]
7891

92+
type EquivalenceClass = IntSet
7993

80-
groupEquivStates :: (Ord a) => DFA Int a -> [IntSet]
94+
groupEquivStates :: forall a. Ord a => DFA Int a -> [EquivalenceClass]
8195
groupEquivStates DFA { dfa_states = statemap }
8296
= go init_p init_q
8397
where
98+
accepting, nonaccepting :: Map Int (State Int a)
8499
(accepting, nonaccepting) = Map.partition acc statemap
85100
where acc (State as _) = not (List.null as)
86101

102+
nonaccepting_states :: EquivalenceClass
87103
nonaccepting_states = IS.fromList (Map.keys nonaccepting)
88104

89105
-- group the accepting states into equivalence classes
106+
accept_map :: Map [Accept a] [Int]
90107
accept_map = {-# SCC "accept_map" #-}
91-
foldl' (\m (n,s) -> Map.insertWith (++) (state_acc s) [n] m)
108+
List.foldl' (\m (n,s) -> Map.insertWith (++) (state_acc s) [n] m)
92109
Map.empty
93110
(Map.toList accepting)
94111

95-
-- accept_groups :: Ord s => [Set s]
112+
accept_groups :: [EquivalenceClass]
96113
accept_groups = map IS.fromList (Map.elems accept_map)
97114

98-
init_p = nonaccepting_states : accept_groups
115+
init_p, init_q :: [EquivalenceClass]
116+
init_p -- Issue #71: each EquivalenceClass needs to be a non-empty set
117+
| IS.null nonaccepting_states = accept_groups
118+
| otherwise = nonaccepting_states : accept_groups
99119
init_q = accept_groups
100120

101121
-- map token T to
@@ -118,6 +138,7 @@ groupEquivStates DFA { dfa_states = statemap }
118138
| s <- IS.toList a ]
119139

120140
-- The outer loop: recurse on each set in Q
141+
go :: [EquivalenceClass] -> [EquivalenceClass] -> [EquivalenceClass]
121142
go p [] = p
122143
go p (a:q) = go1 0 p q
123144
where
@@ -145,6 +166,3 @@ groupEquivStates DFA { dfa_states = statemap }
145166
replaceyin (z:zs)
146167
| z == y = i : d : zs
147168
| otherwise = z : replaceyin zs
148-
149-
150-

tests/Makefile

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -40,6 +40,7 @@ TESTS = \
4040
basic_typeclass_bytestring.x \
4141
default_typeclass.x \
4242
gscan_typeclass.x \
43+
issue_71.x \
4344
monad_typeclass.x \
4445
monad_typeclass_bytestring.x \
4546
monadUserState_typeclass.x \

tests/issue_71.x

Lines changed: 49 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,49 @@
1+
{
2+
-- Issue #71
3+
-- reported 2015-10-20 by Ian Duncan
4+
-- fixed 2020-01-22 by Andreas Abel
5+
--
6+
-- Problem was:
7+
-- DFA minimization crashed with "Prelude head: empty list" because
8+
-- empty set of non-accepting states was treated as empty equivalence
9+
-- class of states.
10+
11+
module Main (main) where
12+
13+
import System.Exit
14+
}
15+
16+
%wrapper "posn"
17+
%token "Token"
18+
19+
$whitespace = [\ \n\t]
20+
@whitespaces = $whitespace*
21+
22+
:-
23+
24+
@whitespaces { \ _ _ -> Whitespaces }
25+
"a" { \ _ _ -> A }
26+
27+
{
28+
data Token = Whitespaces | A
29+
deriving (Eq, Show)
30+
31+
input = "aa \n\taa \t \n a"
32+
expected_result = [A,A,Whitespaces,A,A,Whitespaces,A]
33+
34+
main :: IO ()
35+
main
36+
-- Since the whitespaces token is nullable, Alex
37+
-- will recognize an infinite number of those
38+
-- at the end of file. This behavior is problematic,
39+
-- but we don't fix it here.
40+
-- We just test here whether the expected result
41+
-- is a prefix of the produced result.
42+
| take (length expected_result) result == expected_result = do
43+
exitWith ExitSuccess
44+
| otherwise = do
45+
print $ take 20 result
46+
exitFailure
47+
where
48+
result = alexScanTokens input
49+
}

0 commit comments

Comments
 (0)