/export/starexec/sandbox2/solver/bin/starexec_run_standard /export/starexec/sandbox2/benchmark/theBenchmark.hs /export/starexec/sandbox2/output/output_files -------------------------------------------------------------------------------- MAYBE proof of /export/starexec/sandbox2/benchmark/theBenchmark.hs # AProVE Commit ID: 48fb2092695e11cc9f56e44b17a92a5f88ffb256 marcel 20180622 unpublished dirty H-Termination with start terms of the given HASKELL could not be shown: (0) HASKELL (1) LR [EQUIVALENT, 0 ms] (2) HASKELL (3) CR [EQUIVALENT, 0 ms] (4) HASKELL (5) IFR [EQUIVALENT, 0 ms] (6) HASKELL (7) BR [EQUIVALENT, 0 ms] (8) HASKELL (9) COR [EQUIVALENT, 48 ms] (10) HASKELL (11) LetRed [EQUIVALENT, 9 ms] (12) HASKELL (13) NumRed [SOUND, 46 ms] (14) HASKELL ---------------------------------------- (0) Obligation: mainModule Main module Main where { import qualified Prelude; } ---------------------------------------- (1) LR (EQUIVALENT) Lambda Reductions: The following Lambda expression "\vu24->case vu24 of { (c,''' : []) -> (c,t) : []; _ -> []} " is transformed to "readsPrec0 t vu24 = case vu24 of { (c,''' : []) -> (c,t) : []; _ -> []} ; " The following Lambda expression "\vu25->case vu25 of { (''' : s,t) -> concatMap (readsPrec0 t) (readLitChar s); _ -> []} " is transformed to "readsPrec1 vu25 = case vu25 of { (''' : s,t) -> concatMap (readsPrec0 t) (readLitChar s); _ -> []} ; " The following Lambda expression "\r->concatMap readsPrec1 (lex r)" is transformed to "readsPrec2 r = concatMap readsPrec1 (lex r); " The following Lambda expression "\nd->n * radix + d" is transformed to "readInt0 radix n d = n * radix + d; " The following Lambda expression "\vu77->case vu77 of { (ds,r) -> (foldl1 (readInt0 radix) (map (fromIntegral . digToInt) ds),r) : []; _ -> []} " is transformed to "readInt1 radix digToInt vu77 = case vu77 of { (ds,r) -> (foldl1 (readInt0 radix) (map (fromIntegral . digToInt) ds),r) : []; _ -> []} ; " The following Lambda expression "\vu54->case vu54 of { (ch,''' : t) -> if ch /= ''' : [] then (''' : ch ++ ''' : [],t) : [] else []; _ -> []} " is transformed to "lex0 vu54 = case vu54 of { (ch,''' : t) -> if ch /= ''' : [] then (''' : ch ++ ''' : [],t) : [] else []; _ -> []} ; " The following Lambda expression "\vu56->case vu56 of { (str,u) -> (ch ++ str,u) : []; _ -> []} " is transformed to "lexString0 ch vu56 = case vu56 of { (str,u) -> (ch ++ str,u) : []; _ -> []} ; " The following Lambda expression "\vu57->case vu57 of { (ch,t) -> concatMap (lexString0 ch) (lexString t); _ -> []} " is transformed to "lexString1 vu57 = case vu57 of { (ch,t) -> concatMap (lexString0 ch) (lexString t); _ -> []} ; " The following Lambda expression "\vu58->case vu58 of { '\' : t -> ([],t) : []; _ -> []} " is transformed to "lexStrItem0 vu58 = case vu58 of { '\' : t -> ([],t) : []; _ -> []} ; " The following Lambda expression "\vu55->case vu55 of { (str,t) -> ('"' : str,t) : []; _ -> []} " is transformed to "lex1 vu55 = case vu55 of { (str,t) -> ('"' : str,t) : []; _ -> []} ; " The following Lambda expression "\vu63->case vu63 of { (e,u) -> ('.' : ds ++ e,u) : []; _ -> []} " is transformed to "lexFracExp0 ds vu63 = case vu63 of { (e,u) -> ('.' : ds ++ e,u) : []; _ -> []} ; " The following Lambda expression "\vu64->case vu64 of { (ds,t) -> concatMap (lexFracExp0 ds) (lexExp t); _ -> []} " is transformed to "lexFracExp1 vu64 = case vu64 of { (ds,t) -> concatMap (lexFracExp0 ds) (lexExp t); _ -> []} ; " The following Lambda expression "\vu65->case vu65 of { (ds,u) -> (e : c : ds,u) : []; _ -> []} " is transformed to "lexExp0 e c vu65 = case vu65 of { (ds,u) -> (e : c : ds,u) : []; _ -> []} ; " The following Lambda expression "\vu66->case vu66 of { c : t -> if c `elem` '+' : '-' : [] then concatMap (lexExp0 e c) (lexDigits t) else []; _ -> []} " is transformed to "lexExp1 e vu66 = case vu66 of { c : t -> if c `elem` '+' : '-' : [] then concatMap (lexExp0 e c) (lexDigits t) else []; _ -> []} ; " The following Lambda expression "\vu67->case vu67 of { (ds,t) -> (e : ds,t) : []; _ -> []} " is transformed to "lexExp2 e vu67 = case vu67 of { (ds,t) -> (e : ds,t) : []; _ -> []} ; " The following Lambda expression "\vu59->case vu59 of { (sym,t) -> (c : sym,t) : []; _ -> []} " is transformed to "lex2 c vu59 = case vu59 of { (sym,t) -> (c : sym,t) : []; _ -> []} ; " The following Lambda expression "\vu60->case vu60 of { (nam,t) -> (c : nam,t) : []; _ -> []} " is transformed to "lex3 c vu60 = case vu60 of { (nam,t) -> (c : nam,t) : []; _ -> []} ; " The following Lambda expression "\vu61->case vu61 of { (fe,t) -> (c : ds ++ fe,t) : []; _ -> []} " is transformed to "lex4 c ds vu61 = case vu61 of { (fe,t) -> (c : ds ++ fe,t) : []; _ -> []} ; " The following Lambda expression "\vu62->case vu62 of { (ds,s) -> concatMap (lex4 c ds) (lexFracExp s); _ -> []} " is transformed to "lex5 c vu62 = case vu62 of { (ds,s) -> concatMap (lex4 c ds) (lexFracExp s); _ -> []} ; " The following Lambda expression "\ab->(a,b)" is transformed to "zip0 a b = (a,b); " The following Lambda expression "\vu71->case vu71 of { (n,t) -> (toEnum n,t) : []; _ -> []} " is transformed to "readEsc0 vu71 = case vu71 of { (n,t) -> (toEnum n,t) : []; _ -> []} ; " The following Lambda expression "\vu72->case vu72 of { (n,t) -> (toEnum n,t) : []; _ -> []} " is transformed to "readEsc1 vu72 = case vu72 of { (n,t) -> (toEnum n,t) : []; _ -> []} ; " The following Lambda expression "\vu73->case vu73 of { (n,t) -> (toEnum n,t) : []; _ -> []} " is transformed to "readEsc2 vu73 = case vu73 of { (n,t) -> (toEnum n,t) : []; _ -> []} ; " The following Lambda expression "\vu74->case vu74 of { ([],s') -> (c,s') : []; _ -> []} " is transformed to "readEsc3 c vu74 = case vu74 of { ([],s') -> (c,s') : []; _ -> []} ; " The following Lambda expression "\vu75->case vu75 of { (c,mne) -> concatMap (readEsc3 c) (lexmatch mne s : []); _ -> []} " is transformed to "readEsc4 s vu75 = case vu75 of { (c,mne) -> concatMap (readEsc3 c) (lexmatch mne s : []); _ -> []} ; " The following Lambda expression "\vu68->case vu68 of { (cs@(_ : _),t) -> (cs,t) : []; _ -> []} " is transformed to "nonnull0 vu68 = case vu68 of { (cs@(_ : _),t) -> (cs,t) : []; _ -> []} ; " The following Lambda expression "\d->fromEnum d - fromEnum_0" is transformed to "readOct0 d = fromEnum d - fromEnum_0; " The following Lambda expression "\vu48->case vu48 of { (')' : [],u) -> (x,u) : []; _ -> []} " is transformed to "mandatory0 x vu48 = case vu48 of { (')' : [],u) -> (x,u) : []; _ -> []} ; " The following Lambda expression "\vu49->case vu49 of { (x,t) -> concatMap (mandatory0 x) (lex t); _ -> []} " is transformed to "mandatory1 vu49 = case vu49 of { (x,t) -> concatMap (mandatory0 x) (lex t); _ -> []} ; " The following Lambda expression "\vu50->case vu50 of { ('(' : [],s) -> concatMap mandatory1 (optional s); _ -> []} " is transformed to "mandatory2 vu50 = case vu50 of { ('(' : [],s) -> concatMap mandatory1 (optional s); _ -> []} ; " The following Lambda expression "\d->fromEnum d - fromEnum_0" is transformed to "readDec0 d = fromEnum d - fromEnum_0; " The following Lambda expression "\vu69->case vu69 of { ([],s') -> (mne,s') : []; _ -> []} " is transformed to "lexEsc0 mne vu69 = case vu69 of { ([],s') -> (mne,s') : []; _ -> []} ; " The following Lambda expression "\vu70->case vu70 of { (c,mne) -> concatMap (lexEsc0 mne) (lexmatch mne s : []); _ -> []} " is transformed to "lexEsc1 s vu70 = case vu70 of { (c,mne) -> concatMap (lexEsc0 mne) (lexmatch mne s : []); _ -> []} ; " The following Lambda expression "\(_,zs)->zs" is transformed to "zs0 (_,zs) = zs; " The following Lambda expression "\(ys,_)->ys" is transformed to "ys0 (ys,_) = ys; " ---------------------------------------- (2) Obligation: mainModule Main module Main where { import qualified Prelude; } ---------------------------------------- (3) CR (EQUIVALENT) Case Reductions: The following Case expression "case vu77 of { (ds,r) -> (foldl1 (readInt0 radix) (map (fromIntegral . digToInt) ds),r) : []; _ -> []} " is transformed to "readInt10 radix digToInt (ds,r) = (foldl1 (readInt0 radix) (map (fromIntegral . digToInt) ds),r) : []; readInt10 radix digToInt _ = []; " The following Case expression "case vu55 of { (str,t) -> ('"' : str,t) : []; _ -> []} " is transformed to "lex10 (str,t) = ('"' : str,t) : []; lex10 _ = []; " The following Case expression "case vu57 of { (ch,t) -> concatMap (lexString0 ch) (lexString t); _ -> []} " is transformed to "lexString10 (ch,t) = concatMap (lexString0 ch) (lexString t); lexString10 _ = []; " The following Case expression "case vu56 of { (str,u) -> (ch ++ str,u) : []; _ -> []} " is transformed to "lexString00 ch (str,u) = (ch ++ str,u) : []; lexString00 ch _ = []; " The following Case expression "case vu58 of { '\' : t -> ([],t) : []; _ -> []} " is transformed to "lexStrItem00 ('\' : t) = ([],t) : []; lexStrItem00 _ = []; " The following Case expression "case vu59 of { (sym,t) -> (c : sym,t) : []; _ -> []} " is transformed to "lex20 c (sym,t) = (c : sym,t) : []; lex20 c _ = []; " The following Case expression "case vu67 of { (ds,t) -> (e : ds,t) : []; _ -> []} " is transformed to "lexExp20 e (ds,t) = (e : ds,t) : []; lexExp20 e _ = []; " The following Case expression "case vu65 of { (ds,u) -> (e : c : ds,u) : []; _ -> []} " is transformed to "lexExp00 e c (ds,u) = (e : c : ds,u) : []; lexExp00 e c _ = []; " The following Case expression "case vu62 of { (ds,s) -> concatMap (lex4 c ds) (lexFracExp s); _ -> []} " is transformed to "lex50 c (ds,s) = concatMap (lex4 c ds) (lexFracExp s); lex50 c _ = []; " The following Case expression "case vu66 of { c : t -> if c `elem` '+' : '-' : [] then concatMap (lexExp0 e c) (lexDigits t) else []; _ -> []} " is transformed to "lexExp10 e (c : t) = if c `elem` '+' : '-' : [] then concatMap (lexExp0 e c) (lexDigits t) else []; lexExp10 e _ = []; " The following Case expression "case vu60 of { (nam,t) -> (c : nam,t) : []; _ -> []} " is transformed to "lex30 c (nam,t) = (c : nam,t) : []; lex30 c _ = []; " The following Case expression "case vu61 of { (fe,t) -> (c : ds ++ fe,t) : []; _ -> []} " is transformed to "lex40 c ds (fe,t) = (c : ds ++ fe,t) : []; lex40 c ds _ = []; " The following Case expression "case vu63 of { (e,u) -> ('.' : ds ++ e,u) : []; _ -> []} " is transformed to "lexFracExp00 ds (e,u) = ('.' : ds ++ e,u) : []; lexFracExp00 ds _ = []; " The following Case expression "case vu64 of { (ds,t) -> concatMap (lexFracExp0 ds) (lexExp t); _ -> []} " is transformed to "lexFracExp10 (ds,t) = concatMap (lexFracExp0 ds) (lexExp t); lexFracExp10 _ = []; " The following Case expression "case vu73 of { (n,t) -> (toEnum n,t) : []; _ -> []} " is transformed to "readEsc20 (n,t) = (toEnum n,t) : []; readEsc20 _ = []; " The following Case expression "case vu72 of { (n,t) -> (toEnum n,t) : []; _ -> []} " is transformed to "readEsc10 (n,t) = (toEnum n,t) : []; readEsc10 _ = []; " The following Case expression "case vu71 of { (n,t) -> (toEnum n,t) : []; _ -> []} " is transformed to "readEsc00 (n,t) = (toEnum n,t) : []; readEsc00 _ = []; " The following Case expression "case vu75 of { (c,mne) -> concatMap (readEsc3 c) (lexmatch mne s : []); _ -> []} " is transformed to "readEsc40 s (c,mne) = concatMap (readEsc3 c) (lexmatch mne s : []); readEsc40 s _ = []; " The following Case expression "case vu74 of { ([],s') -> (c,s') : []; _ -> []} " is transformed to "readEsc30 c ([],s') = (c,s') : []; readEsc30 c _ = []; " The following Case expression "case concatMap (readEsc4 s) table of { pr : _ -> pr : []; [] -> []} " is transformed to "readEsc5 (pr : _) = pr : []; readEsc5 [] = []; " The following Case expression "case vu25 of { (''' : s,t) -> concatMap (readsPrec0 t) (readLitChar s); _ -> []} " is transformed to "readsPrec10 (''' : s,t) = concatMap (readsPrec0 t) (readLitChar s); readsPrec10 _ = []; " The following Case expression "case vu24 of { (c,''' : []) -> (c,t) : []; _ -> []} " is transformed to "readsPrec00 t (c,''' : []) = (c,t) : []; readsPrec00 t _ = []; " The following Case expression "case vu54 of { (ch,''' : t) -> if ch /= ''' : [] then (''' : ch ++ ''' : [],t) : [] else []; _ -> []} " is transformed to "lex00 (ch,''' : t) = if ch /= ''' : [] then (''' : ch ++ ''' : [],t) : [] else []; lex00 _ = []; " The following Case expression "case vu48 of { (')' : [],u) -> (x,u) : []; _ -> []} " is transformed to "mandatory00 x (')' : [],u) = (x,u) : []; mandatory00 x _ = []; " The following Case expression "case vu49 of { (x,t) -> concatMap (mandatory0 x) (lex t); _ -> []} " is transformed to "mandatory10 (x,t) = concatMap (mandatory0 x) (lex t); mandatory10 _ = []; " The following Case expression "case vu50 of { ('(' : [],s) -> concatMap mandatory1 (optional s); _ -> []} " is transformed to "mandatory20 ('(' : [],s) = concatMap mandatory1 (optional s); mandatory20 _ = []; " The following Case expression "case vu68 of { (cs@(_ : _),t) -> (cs,t) : []; _ -> []} " is transformed to "nonnull00 (cs@(_ : _),t) = (cs,t) : []; nonnull00 _ = []; " The following Case expression "case concatMap (lexEsc1 s) table of { pr : _ -> pr : []; [] -> []} " is transformed to "lexEsc2 (pr : _) = pr : []; lexEsc2 [] = []; " The following Case expression "case vu69 of { ([],s') -> (mne,s') : []; _ -> []} " is transformed to "lexEsc00 mne ([],s') = (mne,s') : []; lexEsc00 mne _ = []; " The following Case expression "case vu70 of { (c,mne) -> concatMap (lexEsc0 mne) (lexmatch mne s : []); _ -> []} " is transformed to "lexEsc10 s (c,mne) = concatMap (lexEsc0 mne) (lexmatch mne s : []); lexEsc10 s _ = []; " ---------------------------------------- (4) Obligation: mainModule Main module Main where { import qualified Prelude; } ---------------------------------------- (5) IFR (EQUIVALENT) If Reductions: The following If expression "if c `elem` '+' : '-' : [] then concatMap (lexExp0 e c) (lexDigits t) else []" is transformed to "lexExp100 e c t True = concatMap (lexExp0 e c) (lexDigits t); lexExp100 e c t False = []; " The following If expression "if isUpper d then 'A' else 'a'" is transformed to "hex0 True = 'A'; hex0 False = 'a'; " The following If expression "if isDigit d then fromEnum_0 else fromEnum (hex0 (isUpper d)) - 10" is transformed to "hex1 d True = fromEnum_0; hex1 d False = fromEnum (hex0 (isUpper d)) - 10; " The following If expression "if b then mandatory else optional" is transformed to "readParen0 True = mandatory; readParen0 False = optional; " The following If expression "if ch /= ''' : [] then (''' : ch ++ ''' : [],t) : [] else []" is transformed to "lex000 ch t True = (''' : ch ++ ''' : [],t) : []; lex000 ch t False = []; " ---------------------------------------- (6) Obligation: mainModule Main module Main where { import qualified Prelude; } ---------------------------------------- (7) BR (EQUIVALENT) Replaced joker patterns by fresh variables and removed binding patterns. Binding Reductions: The bind variable of the following binding Pattern "cs@(wu : wv)" is replaced by the following term "wu : wv" The bind variable of the following binding Pattern "s@(zv : zw)" is replaced by the following term "zv : zw" The bind variable of the following binding Pattern "s@(zy : zz)" is replaced by the following term "zy : zz" The bind variable of the following binding Pattern "xs@(vwx : vwy)" is replaced by the following term "vwx : vwy" The bind variable of the following binding Pattern "s@(vxv : vxw)" is replaced by the following term "vxv : vxw" The bind variable of the following binding Pattern "xs@(vyv : vyw)" is replaced by the following term "vyv : vyw" ---------------------------------------- (8) Obligation: mainModule Main module Main where { import qualified Prelude; } ---------------------------------------- (9) COR (EQUIVALENT) Cond Reductions: The following Function with conditions "readsPrec00 t (c,''' : []) = (c,t) : []; readsPrec00 t wx = []; " is transformed to "readsPrec00 t (c,vzv : vzw) = readsPrec002 t (c,vzv : vzw); readsPrec00 t wx = readsPrec000 t wx; " "readsPrec000 t wx = []; " "readsPrec001 True t (c,vzv : []) = (c,t) : []; readsPrec001 vzx vzy vzz = readsPrec000 vzy vzz; " "readsPrec002 t (c,vzv : vzw) = readsPrec001 (vzv == ''') t (c,vzv : vzw); readsPrec002 wuu wuv = readsPrec000 wuu wuv; " The following Function with conditions "takeWhile p [] = []; takeWhile p (x : xs)|p xx : takeWhile p xs|otherwise[]; " is transformed to "takeWhile p [] = takeWhile3 p []; takeWhile p (x : xs) = takeWhile2 p (x : xs); " "takeWhile0 p x xs True = []; " "takeWhile1 p x xs True = x : takeWhile p xs; takeWhile1 p x xs False = takeWhile0 p x xs otherwise; " "takeWhile2 p (x : xs) = takeWhile1 p x xs (p x); " "takeWhile3 p [] = []; takeWhile3 wuy wuz = takeWhile2 wuy wuz; " The following Function with conditions "lexString ('"' : s) = ('"' : [],s) : []; lexString s = concatMap lexString1 (lexStrItem s); " is transformed to "lexString (wvv : s) = lexString4 (wvv : s); lexString s = lexString2 s; " "lexString2 s = concatMap lexString1 (lexStrItem s); " "lexString3 True (wvv : s) = ('"' : [],s) : []; lexString3 wvw wvx = lexString2 wvx; " "lexString4 (wvv : s) = lexString3 (wvv == '"') (wvv : s); lexString4 wvy = lexString2 wvy; " The following Function with conditions "lexStrItem ('\' : '&' : s) = ('\' : '&' : [],s) : []; lexStrItem ('\' : c : s)|isSpace cconcatMap lexStrItem0 (dropWhile isSpace s : []); lexStrItem s = lexLitChar s; " is transformed to "lexStrItem (wxw : wyu) = lexStrItem7 (wxw : wyu); lexStrItem (wwu : wwx) = lexStrItem4 (wwu : wwx); lexStrItem s = lexStrItem1 s; " "lexStrItem1 s = lexLitChar s; " "lexStrItem2 wwu c s True = concatMap lexStrItem0 (dropWhile isSpace s : []); lexStrItem2 wwu c s False = lexStrItem1 (wwu : c : s); " "lexStrItem3 True (wwu : c : s) = lexStrItem2 wwu c s (isSpace c); lexStrItem3 wwy wwz = lexStrItem1 wwz; " "lexStrItem4 (wwu : wwx) = lexStrItem3 (wwu == '\') (wwu : wwx); lexStrItem4 wxu = lexStrItem1 wxu; " "lexStrItem5 True (wxw : wxy : s) = ('\' : '&' : [],s) : []; lexStrItem5 wyv wyw = lexStrItem4 wyw; " "lexStrItem6 True (wxw : wxy : s) = lexStrItem5 (wxy == '&') (wxw : wxy : s); lexStrItem6 wyx wyy = lexStrItem4 wyy; " "lexStrItem7 (wxw : wyu) = lexStrItem6 (wxw == '\') (wxw : wyu); lexStrItem7 wyz = lexStrItem4 wyz; " The following Function with conditions "lexStrItem00 ('\' : t) = ([],t) : []; lexStrItem00 xu = []; " is transformed to "lexStrItem00 (wzv : t) = lexStrItem002 (wzv : t); lexStrItem00 xu = lexStrItem000 xu; " "lexStrItem000 xu = []; " "lexStrItem001 True (wzv : t) = ([],t) : []; lexStrItem001 wzw wzx = lexStrItem000 wzx; " "lexStrItem002 (wzv : t) = lexStrItem001 (wzv == '\') (wzv : t); lexStrItem002 wzy = lexStrItem000 wzy; " The following Function with conditions "lexExp (e : s)|e `elem` 'e' : 'E' : []concatMap (lexExp1 e) (s : []) ++ concatMap (lexExp2 e) (lexDigits s); lexExp s = ([],s) : []; " is transformed to "lexExp (e : s) = lexExp5 (e : s); lexExp s = lexExp3 s; " "lexExp3 s = ([],s) : []; " "lexExp4 e s True = concatMap (lexExp1 e) (s : []) ++ concatMap (lexExp2 e) (lexDigits s); lexExp4 e s False = lexExp3 (e : s); " "lexExp5 (e : s) = lexExp4 e s (e `elem` 'e' : 'E' : []); lexExp5 xuu = lexExp3 xuu; " The following Function with conditions "lexFracExp ('.' : c : cs)|isDigit cconcatMap lexFracExp1 (lexDigits (c : cs)); lexFracExp s = lexExp s; " is transformed to "lexFracExp (xuw : xuz) = lexFracExp5 (xuw : xuz); lexFracExp s = lexFracExp2 s; " "lexFracExp2 s = lexExp s; " "lexFracExp3 xuw c cs True = concatMap lexFracExp1 (lexDigits (c : cs)); lexFracExp3 xuw c cs False = lexFracExp2 (xuw : c : cs); " "lexFracExp4 True (xuw : c : cs) = lexFracExp3 xuw c cs (isDigit c); lexFracExp4 xvu xvv = lexFracExp2 xvv; " "lexFracExp5 (xuw : xuz) = lexFracExp4 (xuw == '.') (xuw : xuz); lexFracExp5 xvw = lexFracExp2 xvw; " The following Function with conditions "lex [] = ([],[]) : []; lex (c : s)|isSpace clex (dropWhile isSpace s); lex (''' : s) = concatMap lex0 (lexLitChar s); lex ('"' : s) = concatMap lex1 (lexString s) where { lex1 vu55 = lex10 vu55; ; lex10 (str,t) = ('"' : str,t) : []; lex10 xv = []; ; lexStrItem ('\' : '&' : s) = ('\' : '&' : [],s) : []; lexStrItem ('\' : c : s)|isSpace cconcatMap lexStrItem0 (dropWhile isSpace s : []); lexStrItem s = lexLitChar s; ; lexStrItem0 vu58 = lexStrItem00 vu58; ; lexStrItem00 ('\' : t) = ([],t) : []; lexStrItem00 xu = []; ; lexString ('"' : s) = ('"' : [],s) : []; lexString s = concatMap lexString1 (lexStrItem s); ; lexString0 ch vu56 = lexString00 ch vu56; ; lexString00 ch (str,u) = (ch ++ str,u) : []; lexString00 ch wy = []; ; lexString1 vu57 = lexString10 vu57; ; lexString10 (ch,t) = concatMap (lexString0 ch) (lexString t); lexString10 wz = []; } ; lex (c : s)|isSingle c(c : [],s) : []|isSym cconcatMap (lex2 c) (span isSym s : [])|isAlpha cconcatMap (lex3 c) (span isIdChar s : [])|isDigit cconcatMap (lex5 c) (span isDigit s : [])|otherwise[] where { isIdChar c = isAlphaNum c || c `elem` '_' : ''' : []; ; isSingle c = c `elem` ',' : ';' : '(' : ')' : '[' : ']' : '{' : '}' : '_' : '`' : []; ; isSym c = c `elem` '!' : '@' : '#' : '$' : '%' : '&' : '*' : '+' : '.' : '/' : '<' : '=' : '>' : '?' : '\' : '^' : '|' : ':' : '-' : '~' : []; ; lex2 c vu59 = lex20 c vu59; ; lex20 c (sym,t) = (c : sym,t) : []; lex20 c yx = []; ; lex3 c vu60 = lex30 c vu60; ; lex30 c (nam,t) = (c : nam,t) : []; lex30 c yy = []; ; lex4 c ds vu61 = lex40 c ds vu61; ; lex40 c ds (fe,t) = (c : ds ++ fe,t) : []; lex40 c ds yv = []; ; lex5 c vu62 = lex50 c vu62; ; lex50 c (ds,s) = concatMap (lex4 c ds) (lexFracExp s); lex50 c yw = []; ; lexExp (e : s)|e `elem` 'e' : 'E' : []concatMap (lexExp1 e) (s : []) ++ concatMap (lexExp2 e) (lexDigits s); lexExp s = ([],s) : []; ; lexExp0 e c vu65 = lexExp00 e c vu65; ; lexExp00 e c (ds,u) = (e : c : ds,u) : []; lexExp00 e c xw = []; ; lexExp1 e vu66 = lexExp10 e vu66; ; lexExp10 e (c : t) = lexExp100 e c t (c `elem` '+' : '-' : []); lexExp10 e xy = []; ; lexExp100 e c t True = concatMap (lexExp0 e c) (lexDigits t); lexExp100 e c t False = []; ; lexExp2 e vu67 = lexExp20 e vu67; ; lexExp20 e (ds,t) = (e : ds,t) : []; lexExp20 e xx = []; ; lexFracExp ('.' : c : cs)|isDigit cconcatMap lexFracExp1 (lexDigits (c : cs)); lexFracExp s = lexExp s; ; lexFracExp0 ds vu63 = lexFracExp00 ds vu63; ; lexFracExp00 ds (e,u) = ('.' : ds ++ e,u) : []; lexFracExp00 ds yu = []; ; lexFracExp1 vu64 = lexFracExp10 vu64; ; lexFracExp10 (ds,t) = concatMap (lexFracExp0 ds) (lexExp t); lexFracExp10 xz = []; } ; " is transformed to "lex [] = lex19 []; lex (c : s) = lex18 (c : s); lex (xwy : s) = lex16 (xwy : s); lex (xvz : s) = lex14 (xvz : s); lex (c : s) = lex12 (c : s); " "lex12 (c : s) = lex11 c s (isSingle c) where { isIdChar c = isAlphaNum c || c `elem` '_' : ''' : []; ; isSingle c = c `elem` ',' : ';' : '(' : ')' : '[' : ']' : '{' : '}' : '_' : '`' : []; ; isSym c = c `elem` '!' : '@' : '#' : '$' : '%' : '&' : '*' : '+' : '.' : '/' : '<' : '=' : '>' : '?' : '\' : '^' : '|' : ':' : '-' : '~' : []; ; lex11 c s True = (c : [],s) : []; lex11 c s False = lex9 c s (isSym c); ; lex2 c vu59 = lex20 c vu59; ; lex20 c (sym,t) = (c : sym,t) : []; lex20 c yx = []; ; lex3 c vu60 = lex30 c vu60; ; lex30 c (nam,t) = (c : nam,t) : []; lex30 c yy = []; ; lex4 c ds vu61 = lex40 c ds vu61; ; lex40 c ds (fe,t) = (c : ds ++ fe,t) : []; lex40 c ds yv = []; ; lex5 c vu62 = lex50 c vu62; ; lex50 c (ds,s) = concatMap (lex4 c ds) (lexFracExp s); lex50 c yw = []; ; lex6 c s True = []; ; lex7 c s True = concatMap (lex5 c) (span isDigit s : []); lex7 c s False = lex6 c s otherwise; ; lex8 c s True = concatMap (lex3 c) (span isIdChar s : []); lex8 c s False = lex7 c s (isDigit c); ; lex9 c s True = concatMap (lex2 c) (span isSym s : []); lex9 c s False = lex8 c s (isAlpha c); ; lexExp (e : s) = lexExp5 (e : s); lexExp s = lexExp3 s; ; lexExp0 e c vu65 = lexExp00 e c vu65; ; lexExp00 e c (ds,u) = (e : c : ds,u) : []; lexExp00 e c xw = []; ; lexExp1 e vu66 = lexExp10 e vu66; ; lexExp10 e (c : t) = lexExp100 e c t (c `elem` '+' : '-' : []); lexExp10 e xy = []; ; lexExp100 e c t True = concatMap (lexExp0 e c) (lexDigits t); lexExp100 e c t False = []; ; lexExp2 e vu67 = lexExp20 e vu67; ; lexExp20 e (ds,t) = (e : ds,t) : []; lexExp20 e xx = []; ; lexExp3 s = ([],s) : []; ; lexExp4 e s True = concatMap (lexExp1 e) (s : []) ++ concatMap (lexExp2 e) (lexDigits s); lexExp4 e s False = lexExp3 (e : s); ; lexExp5 (e : s) = lexExp4 e s (e `elem` 'e' : 'E' : []); lexExp5 xuu = lexExp3 xuu; ; lexFracExp (xuw : xuz) = lexFracExp5 (xuw : xuz); lexFracExp s = lexFracExp2 s; ; lexFracExp0 ds vu63 = lexFracExp00 ds vu63; ; lexFracExp00 ds (e,u) = ('.' : ds ++ e,u) : []; lexFracExp00 ds yu = []; ; lexFracExp1 vu64 = lexFracExp10 vu64; ; lexFracExp10 (ds,t) = concatMap (lexFracExp0 ds) (lexExp t); lexFracExp10 xz = []; ; lexFracExp2 s = lexExp s; ; lexFracExp3 xuw c cs True = concatMap lexFracExp1 (lexDigits (c : cs)); lexFracExp3 xuw c cs False = lexFracExp2 (xuw : c : cs); ; lexFracExp4 True (xuw : c : cs) = lexFracExp3 xuw c cs (isDigit c); lexFracExp4 xvu xvv = lexFracExp2 xvv; ; lexFracExp5 (xuw : xuz) = lexFracExp4 (xuw == '.') (xuw : xuz); lexFracExp5 xvw = lexFracExp2 xvw; } ; " "lex13 True (xvz : s) = concatMap lex1 (lexString s) where { lex1 vu55 = lex10 vu55; ; lex10 (str,t) = ('"' : str,t) : []; lex10 xv = []; ; lexStrItem (wxw : wyu) = lexStrItem7 (wxw : wyu); lexStrItem (wwu : wwx) = lexStrItem4 (wwu : wwx); lexStrItem s = lexStrItem1 s; ; lexStrItem0 vu58 = lexStrItem00 vu58; ; lexStrItem00 (wzv : t) = lexStrItem002 (wzv : t); lexStrItem00 xu = lexStrItem000 xu; ; lexStrItem000 xu = []; ; lexStrItem001 True (wzv : t) = ([],t) : []; lexStrItem001 wzw wzx = lexStrItem000 wzx; ; lexStrItem002 (wzv : t) = lexStrItem001 (wzv == '\') (wzv : t); lexStrItem002 wzy = lexStrItem000 wzy; ; lexStrItem1 s = lexLitChar s; ; lexStrItem2 wwu c s True = concatMap lexStrItem0 (dropWhile isSpace s : []); lexStrItem2 wwu c s False = lexStrItem1 (wwu : c : s); ; lexStrItem3 True (wwu : c : s) = lexStrItem2 wwu c s (isSpace c); lexStrItem3 wwy wwz = lexStrItem1 wwz; ; lexStrItem4 (wwu : wwx) = lexStrItem3 (wwu == '\') (wwu : wwx); lexStrItem4 wxu = lexStrItem1 wxu; ; lexStrItem5 True (wxw : wxy : s) = ('\' : '&' : [],s) : []; lexStrItem5 wyv wyw = lexStrItem4 wyw; ; lexStrItem6 True (wxw : wxy : s) = lexStrItem5 (wxy == '&') (wxw : wxy : s); lexStrItem6 wyx wyy = lexStrItem4 wyy; ; lexStrItem7 (wxw : wyu) = lexStrItem6 (wxw == '\') (wxw : wyu); lexStrItem7 wyz = lexStrItem4 wyz; ; lexString (wvv : s) = lexString4 (wvv : s); lexString s = lexString2 s; ; lexString0 ch vu56 = lexString00 ch vu56; ; lexString00 ch (str,u) = (ch ++ str,u) : []; lexString00 ch wy = []; ; lexString1 vu57 = lexString10 vu57; ; lexString10 (ch,t) = concatMap (lexString0 ch) (lexString t); lexString10 wz = []; ; lexString2 s = concatMap lexString1 (lexStrItem s); ; lexString3 True (wvv : s) = ('"' : [],s) : []; lexString3 wvw wvx = lexString2 wvx; ; lexString4 (wvv : s) = lexString3 (wvv == '"') (wvv : s); lexString4 wvy = lexString2 wvy; } ; lex13 xwu xwv = lex12 xwv; " "lex14 (xvz : s) = lex13 (xvz == '"') (xvz : s); lex14 xww = lex12 xww; " "lex15 True (xwy : s) = concatMap lex0 (lexLitChar s); lex15 xwz xxu = lex14 xxu; " "lex16 (xwy : s) = lex15 (xwy == ''') (xwy : s); lex16 xxv = lex14 xxv; " "lex17 c s True = lex (dropWhile isSpace s); lex17 c s False = lex16 (c : s); " "lex18 (c : s) = lex17 c s (isSpace c); lex18 xxx = lex16 xxx; " "lex19 [] = ([],[]) : []; lex19 xxz = lex18 xxz; " The following Function with conditions "readsPrec10 (''' : s,t) = concatMap (readsPrec0 t) (readLitChar s); readsPrec10 yz = []; " is transformed to "readsPrec10 (xyw : s,t) = readsPrec102 (xyw : s,t); readsPrec10 yz = readsPrec100 yz; " "readsPrec100 yz = []; " "readsPrec101 True (xyw : s,t) = concatMap (readsPrec0 t) (readLitChar s); readsPrec101 xyx xyy = readsPrec100 xyy; " "readsPrec102 (xyw : s,t) = readsPrec101 (xyw == ''') (xyw : s,t); readsPrec102 xyz = readsPrec100 xyz; " The following Function with conditions "readEsc ('a' : s) = ('\7',s) : []; readEsc ('b' : s) = ('\8',s) : []; readEsc ('f' : s) = ('\12',s) : []; readEsc ('n' : s) = ('\10',s) : []; readEsc ('r' : s) = ('\13',s) : []; readEsc ('t' : s) = ('\9',s) : []; readEsc ('v' : s) = ('\11',s) : []; readEsc ('\' : s) = ('\',s) : []; readEsc ('"' : s) = ('"',s) : []; readEsc (''' : s) = (''',s) : []; readEsc ('^' : c : s)|c >= '@' && c <= '_'(toEnum (fromEnum c - fromEnum '@'),s) : []; readEsc (zv : zw)|isDigit zvconcatMap readEsc0 (readDec (zv : zw)); readEsc ('o' : s) = concatMap readEsc1 (readOct s); readEsc ('x' : s) = concatMap readEsc2 (readHex s); readEsc (zy : zz)|isUpper zylet { readEsc3 c vu74 = readEsc30 c vu74; ; readEsc30 c ([],s') = (c,s') : []; readEsc30 c vuw = []; ; readEsc4 s vu75 = readEsc40 s vu75; ; readEsc40 s (c,mne) = concatMap (readEsc3 c) (lexmatch mne s : []); readEsc40 s vuv = []; ; readEsc5 (pr : vuu) = pr : []; readEsc5 [] = []; ; table = ('\127','D' : 'E' : 'L' : []) : asciiTab; } in readEsc5 (concatMap (readEsc4 (zy : zz)) table); readEsc vux = []; " is transformed to "readEsc (zyw : s) = readEsc41 (zyw : s); readEsc (zxx : s) = readEsc38 (zxx : s); readEsc (zwy : s) = readEsc36 (zwy : s); readEsc (zvz : s) = readEsc34 (zvz : s); readEsc (zvu : s) = readEsc32 (zvu : s); readEsc (zuv : s) = readEsc29 (zuv : s); readEsc (yzw : s) = readEsc27 (yzw : s); readEsc (yyx : s) = readEsc25 (yyx : s); readEsc (yxy : s) = readEsc23 (yxy : s); readEsc (ywz : s) = readEsc21 (ywz : s); readEsc (yvx : ywu) = readEsc18 (yvx : ywu); readEsc (zv : zw) = readEsc15 (zv : zw); readEsc (yuw : s) = readEsc13 (yuw : s); readEsc (xzx : s) = readEsc11 (xzx : s); readEsc (zy : zz) = readEsc8 (zy : zz); readEsc vux = readEsc6 vux; " "readEsc6 vux = []; " "readEsc7 zy zz True = let { readEsc3 c vu74 = readEsc30 c vu74; ; readEsc30 c ([],s') = (c,s') : []; readEsc30 c vuw = []; ; readEsc4 s vu75 = readEsc40 s vu75; ; readEsc40 s (c,mne) = concatMap (readEsc3 c) (lexmatch mne s : []); readEsc40 s vuv = []; ; readEsc5 (pr : vuu) = pr : []; readEsc5 [] = []; ; table = ('\127','D' : 'E' : 'L' : []) : asciiTab; } in readEsc5 (concatMap (readEsc4 (zy : zz)) table); readEsc7 zy zz False = readEsc6 (zy : zz); " "readEsc8 (zy : zz) = readEsc7 zy zz (isUpper zy); readEsc8 xzv = readEsc6 xzv; " "readEsc9 True (xzx : s) = concatMap readEsc2 (readHex s); readEsc9 xzy xzz = readEsc8 xzz; " "readEsc11 (xzx : s) = readEsc9 (xzx == 'x') (xzx : s); readEsc11 yuu = readEsc8 yuu; " "readEsc12 True (yuw : s) = concatMap readEsc1 (readOct s); readEsc12 yux yuy = readEsc11 yuy; " "readEsc13 (yuw : s) = readEsc12 (yuw == 'o') (yuw : s); readEsc13 yuz = readEsc11 yuz; " "readEsc14 zv zw True = concatMap readEsc0 (readDec (zv : zw)); readEsc14 zv zw False = readEsc13 (zv : zw); " "readEsc15 (zv : zw) = readEsc14 zv zw (isDigit zv); readEsc15 yvv = readEsc13 yvv; " "readEsc16 yvx c s True = (toEnum (fromEnum c - fromEnum '@'),s) : []; readEsc16 yvx c s False = readEsc15 (yvx : c : s); " "readEsc17 True (yvx : c : s) = readEsc16 yvx c s (c >= '@' && c <= '_'); readEsc17 ywv yww = readEsc15 yww; " "readEsc18 (yvx : ywu) = readEsc17 (yvx == '^') (yvx : ywu); readEsc18 ywx = readEsc15 ywx; " "readEsc19 True (ywz : s) = (''',s) : []; readEsc19 yxu yxv = readEsc18 yxv; " "readEsc21 (ywz : s) = readEsc19 (ywz == ''') (ywz : s); readEsc21 yxw = readEsc18 yxw; " "readEsc22 True (yxy : s) = ('"',s) : []; readEsc22 yxz yyu = readEsc21 yyu; " "readEsc23 (yxy : s) = readEsc22 (yxy == '"') (yxy : s); readEsc23 yyv = readEsc21 yyv; " "readEsc24 True (yyx : s) = ('\',s) : []; readEsc24 yyy yyz = readEsc23 yyz; " "readEsc25 (yyx : s) = readEsc24 (yyx == '\') (yyx : s); readEsc25 yzu = readEsc23 yzu; " "readEsc26 True (yzw : s) = ('\11',s) : []; readEsc26 yzx yzy = readEsc25 yzy; " "readEsc27 (yzw : s) = readEsc26 (yzw == 'v') (yzw : s); readEsc27 yzz = readEsc25 yzz; " "readEsc28 True (zuv : s) = ('\9',s) : []; readEsc28 zuw zux = readEsc27 zux; " "readEsc29 (zuv : s) = readEsc28 (zuv == 't') (zuv : s); readEsc29 zuy = readEsc27 zuy; " "readEsc31 True (zvu : s) = ('\13',s) : []; readEsc31 zvv zvw = readEsc29 zvw; " "readEsc32 (zvu : s) = readEsc31 (zvu == 'r') (zvu : s); readEsc32 zvx = readEsc29 zvx; " "readEsc33 True (zvz : s) = ('\10',s) : []; readEsc33 zwu zwv = readEsc32 zwv; " "readEsc34 (zvz : s) = readEsc33 (zvz == 'n') (zvz : s); readEsc34 zww = readEsc32 zww; " "readEsc35 True (zwy : s) = ('\12',s) : []; readEsc35 zwz zxu = readEsc34 zxu; " "readEsc36 (zwy : s) = readEsc35 (zwy == 'f') (zwy : s); readEsc36 zxv = readEsc34 zxv; " "readEsc37 True (zxx : s) = ('\8',s) : []; readEsc37 zxy zxz = readEsc36 zxz; " "readEsc38 (zxx : s) = readEsc37 (zxx == 'b') (zxx : s); readEsc38 zyu = readEsc36 zyu; " "readEsc39 True (zyw : s) = ('\7',s) : []; readEsc39 zyx zyy = readEsc38 zyy; " "readEsc41 (zyw : s) = readEsc39 (zyw == 'a') (zyw : s); readEsc41 zyz = readEsc38 zyz; " The following Function with conditions "readLitChar ('\' : s) = readEsc s where { readEsc ('a' : s) = ('\7',s) : []; readEsc ('b' : s) = ('\8',s) : []; readEsc ('f' : s) = ('\12',s) : []; readEsc ('n' : s) = ('\10',s) : []; readEsc ('r' : s) = ('\13',s) : []; readEsc ('t' : s) = ('\9',s) : []; readEsc ('v' : s) = ('\11',s) : []; readEsc ('\' : s) = ('\',s) : []; readEsc ('"' : s) = ('"',s) : []; readEsc (''' : s) = (''',s) : []; readEsc ('^' : c : s)|c >= '@' && c <= '_'(toEnum (fromEnum c - fromEnum '@'),s) : []; readEsc (zv : zw)|isDigit zvconcatMap readEsc0 (readDec (zv : zw)); readEsc ('o' : s) = concatMap readEsc1 (readOct s); readEsc ('x' : s) = concatMap readEsc2 (readHex s); readEsc (zy : zz)|isUpper zylet { readEsc3 c vu74 = readEsc30 c vu74; ; readEsc30 c ([],s') = (c,s') : []; readEsc30 c vuw = []; ; readEsc4 s vu75 = readEsc40 s vu75; ; readEsc40 s (c,mne) = concatMap (readEsc3 c) (lexmatch mne s : []); readEsc40 s vuv = []; ; readEsc5 (pr : vuu) = pr : []; readEsc5 [] = []; ; table = ('\127','D' : 'E' : 'L' : []) : asciiTab; } in readEsc5 (concatMap (readEsc4 (zy : zz)) table); readEsc vux = []; ; readEsc0 vu71 = readEsc00 vu71; ; readEsc00 (n,t) = (toEnum n,t) : []; readEsc00 vuy = []; ; readEsc1 vu72 = readEsc10 vu72; ; readEsc10 (n,t) = (toEnum n,t) : []; readEsc10 vuz = []; ; readEsc2 vu73 = readEsc20 vu73; ; readEsc20 (n,t) = (toEnum n,t) : []; readEsc20 vvu = []; } ; readLitChar (c : s) = (c,s) : []; " is transformed to "readLitChar (zzw : s) = readLitChar2 (zzw : s); readLitChar (c : s) = readLitChar0 (c : s); " "readLitChar0 (c : s) = (c,s) : []; " "readLitChar1 True (zzw : s) = readEsc s where { readEsc (zyw : s) = readEsc41 (zyw : s); readEsc (zxx : s) = readEsc38 (zxx : s); readEsc (zwy : s) = readEsc36 (zwy : s); readEsc (zvz : s) = readEsc34 (zvz : s); readEsc (zvu : s) = readEsc32 (zvu : s); readEsc (zuv : s) = readEsc29 (zuv : s); readEsc (yzw : s) = readEsc27 (yzw : s); readEsc (yyx : s) = readEsc25 (yyx : s); readEsc (yxy : s) = readEsc23 (yxy : s); readEsc (ywz : s) = readEsc21 (ywz : s); readEsc (yvx : ywu) = readEsc18 (yvx : ywu); readEsc (zv : zw) = readEsc15 (zv : zw); readEsc (yuw : s) = readEsc13 (yuw : s); readEsc (xzx : s) = readEsc11 (xzx : s); readEsc (zy : zz) = readEsc8 (zy : zz); readEsc vux = readEsc6 vux; ; readEsc0 vu71 = readEsc00 vu71; ; readEsc00 (n,t) = (toEnum n,t) : []; readEsc00 vuy = []; ; readEsc1 vu72 = readEsc10 vu72; ; readEsc10 (n,t) = (toEnum n,t) : []; readEsc10 vuz = []; ; readEsc11 (xzx : s) = readEsc9 (xzx == 'x') (xzx : s); readEsc11 yuu = readEsc8 yuu; ; readEsc12 True (yuw : s) = concatMap readEsc1 (readOct s); readEsc12 yux yuy = readEsc11 yuy; ; readEsc13 (yuw : s) = readEsc12 (yuw == 'o') (yuw : s); readEsc13 yuz = readEsc11 yuz; ; readEsc14 zv zw True = concatMap readEsc0 (readDec (zv : zw)); readEsc14 zv zw False = readEsc13 (zv : zw); ; readEsc15 (zv : zw) = readEsc14 zv zw (isDigit zv); readEsc15 yvv = readEsc13 yvv; ; readEsc16 yvx c s True = (toEnum (fromEnum c - fromEnum '@'),s) : []; readEsc16 yvx c s False = readEsc15 (yvx : c : s); ; readEsc17 True (yvx : c : s) = readEsc16 yvx c s (c >= '@' && c <= '_'); readEsc17 ywv yww = readEsc15 yww; ; readEsc18 (yvx : ywu) = readEsc17 (yvx == '^') (yvx : ywu); readEsc18 ywx = readEsc15 ywx; ; readEsc19 True (ywz : s) = (''',s) : []; readEsc19 yxu yxv = readEsc18 yxv; ; readEsc2 vu73 = readEsc20 vu73; ; readEsc20 (n,t) = (toEnum n,t) : []; readEsc20 vvu = []; ; readEsc21 (ywz : s) = readEsc19 (ywz == ''') (ywz : s); readEsc21 yxw = readEsc18 yxw; ; readEsc22 True (yxy : s) = ('"',s) : []; readEsc22 yxz yyu = readEsc21 yyu; ; readEsc23 (yxy : s) = readEsc22 (yxy == '"') (yxy : s); readEsc23 yyv = readEsc21 yyv; ; readEsc24 True (yyx : s) = ('\',s) : []; readEsc24 yyy yyz = readEsc23 yyz; ; readEsc25 (yyx : s) = readEsc24 (yyx == '\') (yyx : s); readEsc25 yzu = readEsc23 yzu; ; readEsc26 True (yzw : s) = ('\11',s) : []; readEsc26 yzx yzy = readEsc25 yzy; ; readEsc27 (yzw : s) = readEsc26 (yzw == 'v') (yzw : s); readEsc27 yzz = readEsc25 yzz; ; readEsc28 True (zuv : s) = ('\9',s) : []; readEsc28 zuw zux = readEsc27 zux; ; readEsc29 (zuv : s) = readEsc28 (zuv == 't') (zuv : s); readEsc29 zuy = readEsc27 zuy; ; readEsc31 True (zvu : s) = ('\13',s) : []; readEsc31 zvv zvw = readEsc29 zvw; ; readEsc32 (zvu : s) = readEsc31 (zvu == 'r') (zvu : s); readEsc32 zvx = readEsc29 zvx; ; readEsc33 True (zvz : s) = ('\10',s) : []; readEsc33 zwu zwv = readEsc32 zwv; ; readEsc34 (zvz : s) = readEsc33 (zvz == 'n') (zvz : s); readEsc34 zww = readEsc32 zww; ; readEsc35 True (zwy : s) = ('\12',s) : []; readEsc35 zwz zxu = readEsc34 zxu; ; readEsc36 (zwy : s) = readEsc35 (zwy == 'f') (zwy : s); readEsc36 zxv = readEsc34 zxv; ; readEsc37 True (zxx : s) = ('\8',s) : []; readEsc37 zxy zxz = readEsc36 zxz; ; readEsc38 (zxx : s) = readEsc37 (zxx == 'b') (zxx : s); readEsc38 zyu = readEsc36 zyu; ; readEsc39 True (zyw : s) = ('\7',s) : []; readEsc39 zyx zyy = readEsc38 zyy; ; readEsc41 (zyw : s) = readEsc39 (zyw == 'a') (zyw : s); readEsc41 zyz = readEsc38 zyz; ; readEsc6 vux = []; ; readEsc7 zy zz True = let { readEsc3 c vu74 = readEsc30 c vu74; ; readEsc30 c ([],s') = (c,s') : []; readEsc30 c vuw = []; ; readEsc4 s vu75 = readEsc40 s vu75; ; readEsc40 s (c,mne) = concatMap (readEsc3 c) (lexmatch mne s : []); readEsc40 s vuv = []; ; readEsc5 (pr : vuu) = pr : []; readEsc5 [] = []; ; table = ('\127','D' : 'E' : 'L' : []) : asciiTab; } in readEsc5 (concatMap (readEsc4 (zy : zz)) table); readEsc7 zy zz False = readEsc6 (zy : zz); ; readEsc8 (zy : zz) = readEsc7 zy zz (isUpper zy); readEsc8 xzv = readEsc6 xzv; ; readEsc9 True (xzx : s) = concatMap readEsc2 (readHex s); readEsc9 xzy xzz = readEsc8 xzz; } ; readLitChar1 zzx zzy = readLitChar0 zzy; " "readLitChar2 (zzw : s) = readLitChar1 (zzw == '\') (zzw : s); readLitChar2 zzz = readLitChar0 zzz; " The following Function with conditions "lexmatch (x : xs) (y : ys)|x == ylexmatch xs ys; lexmatch xs ys = (xs,ys); " is transformed to "lexmatch (x : xs) (y : ys) = lexmatch2 (x : xs) (y : ys); lexmatch xs ys = lexmatch0 xs ys; " "lexmatch0 xs ys = (xs,ys); " "lexmatch1 x xs y ys True = lexmatch xs ys; lexmatch1 x xs y ys False = lexmatch0 (x : xs) (y : ys); " "lexmatch2 (x : xs) (y : ys) = lexmatch1 x xs y ys (x == y); lexmatch2 vuuw vuux = lexmatch0 vuuw vuux; " The following Function with conditions "undefined |Falseundefined; " is transformed to "undefined = undefined1; " "undefined0 True = undefined; " "undefined1 = undefined0 False; " The following Function with conditions "mandatory20 ('(' : [],s) = concatMap mandatory1 (optional s); mandatory20 vwu = []; " is transformed to "mandatory20 (vuvu : vuvv,s) = mandatory202 (vuvu : vuvv,s); mandatory20 vwu = mandatory200 vwu; " "mandatory200 vwu = []; " "mandatory201 True (vuvu : [],s) = concatMap mandatory1 (optional s); mandatory201 vuvw vuvx = mandatory200 vuvx; " "mandatory202 (vuvu : vuvv,s) = mandatory201 (vuvu == '(') (vuvu : vuvv,s); mandatory202 vuvy = mandatory200 vuvy; " The following Function with conditions "mandatory00 x (')' : [],u) = (x,u) : []; mandatory00 x vwv = []; " is transformed to "mandatory00 x (vuwv : vuww,u) = mandatory002 x (vuwv : vuww,u); mandatory00 x vwv = mandatory000 x vwv; " "mandatory000 x vwv = []; " "mandatory001 True x (vuwv : [],u) = (x,u) : []; mandatory001 vuwx vuwy vuwz = mandatory000 vuwy vuwz; " "mandatory002 x (vuwv : vuww,u) = mandatory001 (vuwv == ')') x (vuwv : vuww,u); mandatory002 vuxu vuxv = mandatory000 vuxu vuxv; " The following Function with conditions "dropWhile p [] = []; dropWhile p (vwx : vwy)|p vwxdropWhile p vwy|otherwisevwx : vwy; " is transformed to "dropWhile p [] = dropWhile3 p []; dropWhile p (vwx : vwy) = dropWhile2 p (vwx : vwy); " "dropWhile0 p vwx vwy True = vwx : vwy; " "dropWhile1 p vwx vwy True = dropWhile p vwy; dropWhile1 p vwx vwy False = dropWhile0 p vwx vwy otherwise; " "dropWhile2 p (vwx : vwy) = dropWhile1 p vwx vwy (p vwx); " "dropWhile3 p [] = []; dropWhile3 vuxy vuxz = dropWhile2 vuxy vuxz; " The following Function with conditions "lex00 (ch,''' : t) = lex000 ch t (ch /= ''' : []); lex00 vwz = []; " is transformed to "lex00 (ch,vuyw : t) = lex003 (ch,vuyw : t); lex00 vwz = lex001 vwz; " "lex001 vwz = []; " "lex002 True (ch,vuyw : t) = lex000 ch t (ch /= ''' : []); lex002 vuyx vuyy = lex001 vuyy; " "lex003 (ch,vuyw : t) = lex002 (vuyw == ''') (ch,vuyw : t); lex003 vuyz = lex001 vuyz; " The following Function with conditions "lexEsc (c : s)|c `elem` 'a' : 'b' : 'f' : 'n' : 'r' : 't' : 'v' : '\' : '"' : ''' : [](c : [],s) : []; lexEsc ('^' : c : s)|c >= '@' && c <= '_'('^' : c : [],s) : []; lexEsc ('o' : s) = prefix 'o' (span isOctDigit s) : []; lexEsc ('x' : s) = prefix 'x' (span isHexDigit s) : []; lexEsc (vxv : vxw)|isDigit vxvspan isDigit (vxv : vxw) : []|isUpper vxvlexEsc2 (concatMap (lexEsc1 (vxv : vxw)) table); lexEsc vxx = []; " is transformed to "lexEsc (c : s) = lexEsc16 (c : s); lexEsc (vvvv : vvvy) = lexEsc14 (vvvv : vvvy); lexEsc (vvuw : s) = lexEsc11 (vvuw : s); lexEsc (vuzx : s) = lexEsc8 (vuzx : s); lexEsc (vxv : vxw) = lexEsc6 (vxv : vxw); lexEsc vxx = lexEsc3 vxx; " "lexEsc3 vxx = []; " "lexEsc4 vxv vxw True = lexEsc2 (concatMap (lexEsc1 (vxv : vxw)) table); lexEsc4 vxv vxw False = lexEsc3 (vxv : vxw); " "lexEsc5 vxv vxw True = span isDigit (vxv : vxw) : []; lexEsc5 vxv vxw False = lexEsc4 vxv vxw (isUpper vxv); " "lexEsc6 (vxv : vxw) = lexEsc5 vxv vxw (isDigit vxv); lexEsc6 vuzv = lexEsc3 vuzv; " "lexEsc7 True (vuzx : s) = prefix 'x' (span isHexDigit s) : []; lexEsc7 vuzy vuzz = lexEsc6 vuzz; " "lexEsc8 (vuzx : s) = lexEsc7 (vuzx == 'x') (vuzx : s); lexEsc8 vvuu = lexEsc6 vvuu; " "lexEsc9 True (vvuw : s) = prefix 'o' (span isOctDigit s) : []; lexEsc9 vvux vvuy = lexEsc8 vvuy; " "lexEsc11 (vvuw : s) = lexEsc9 (vvuw == 'o') (vvuw : s); lexEsc11 vvuz = lexEsc8 vvuz; " "lexEsc12 vvvv c s True = ('^' : c : [],s) : []; lexEsc12 vvvv c s False = lexEsc11 (vvvv : c : s); " "lexEsc13 True (vvvv : c : s) = lexEsc12 vvvv c s (c >= '@' && c <= '_'); lexEsc13 vvvz vvwu = lexEsc11 vvwu; " "lexEsc14 (vvvv : vvvy) = lexEsc13 (vvvv == '^') (vvvv : vvvy); lexEsc14 vvwv = lexEsc11 vvwv; " "lexEsc15 c s True = (c : [],s) : []; lexEsc15 c s False = lexEsc14 (c : s); " "lexEsc16 (c : s) = lexEsc15 c s (c `elem` 'a' : 'b' : 'f' : 'n' : 'r' : 't' : 'v' : '\' : '"' : ''' : []); lexEsc16 vvwx = lexEsc14 vvwx; " The following Function with conditions "lexLitChar [] = []; lexLitChar (c : s)|c /= '\'(c : [],s) : []|otherwisemap (prefix '\') (lexEsc s) where { lexEsc (c : s)|c `elem` 'a' : 'b' : 'f' : 'n' : 'r' : 't' : 'v' : '\' : '"' : ''' : [](c : [],s) : []; lexEsc ('^' : c : s)|c >= '@' && c <= '_'('^' : c : [],s) : []; lexEsc ('o' : s) = prefix 'o' (span isOctDigit s) : []; lexEsc ('x' : s) = prefix 'x' (span isHexDigit s) : []; lexEsc (vxv : vxw)|isDigit vxvspan isDigit (vxv : vxw) : []|isUpper vxvlexEsc2 (concatMap (lexEsc1 (vxv : vxw)) table); lexEsc vxx = []; ; lexEsc0 mne vu69 = lexEsc00 mne vu69; ; lexEsc00 mne ([],s') = (mne,s') : []; lexEsc00 mne vxz = []; ; lexEsc1 s vu70 = lexEsc10 s vu70; ; lexEsc10 s (c,mne) = concatMap (lexEsc0 mne) (lexmatch mne s : []); lexEsc10 s vyu = []; ; lexEsc2 (pr : vxy) = pr : []; lexEsc2 [] = []; ; prefix c (t,s) = (c : t,s); ; table = ('\127','D' : 'E' : 'L' : []) : asciiTab; } ; " is transformed to "lexLitChar [] = lexLitChar3 []; lexLitChar (c : s) = lexLitChar2 (c : s); " "lexLitChar2 (c : s) = lexLitChar1 c s (c /= '\') where { lexEsc (c : s) = lexEsc16 (c : s); lexEsc (vvvv : vvvy) = lexEsc14 (vvvv : vvvy); lexEsc (vvuw : s) = lexEsc11 (vvuw : s); lexEsc (vuzx : s) = lexEsc8 (vuzx : s); lexEsc (vxv : vxw) = lexEsc6 (vxv : vxw); lexEsc vxx = lexEsc3 vxx; ; lexEsc0 mne vu69 = lexEsc00 mne vu69; ; lexEsc00 mne ([],s') = (mne,s') : []; lexEsc00 mne vxz = []; ; lexEsc1 s vu70 = lexEsc10 s vu70; ; lexEsc10 s (c,mne) = concatMap (lexEsc0 mne) (lexmatch mne s : []); lexEsc10 s vyu = []; ; lexEsc11 (vvuw : s) = lexEsc9 (vvuw == 'o') (vvuw : s); lexEsc11 vvuz = lexEsc8 vvuz; ; lexEsc12 vvvv c s True = ('^' : c : [],s) : []; lexEsc12 vvvv c s False = lexEsc11 (vvvv : c : s); ; lexEsc13 True (vvvv : c : s) = lexEsc12 vvvv c s (c >= '@' && c <= '_'); lexEsc13 vvvz vvwu = lexEsc11 vvwu; ; lexEsc14 (vvvv : vvvy) = lexEsc13 (vvvv == '^') (vvvv : vvvy); lexEsc14 vvwv = lexEsc11 vvwv; ; lexEsc15 c s True = (c : [],s) : []; lexEsc15 c s False = lexEsc14 (c : s); ; lexEsc16 (c : s) = lexEsc15 c s (c `elem` 'a' : 'b' : 'f' : 'n' : 'r' : 't' : 'v' : '\' : '"' : ''' : []); lexEsc16 vvwx = lexEsc14 vvwx; ; lexEsc2 (pr : vxy) = pr : []; lexEsc2 [] = []; ; lexEsc3 vxx = []; ; lexEsc4 vxv vxw True = lexEsc2 (concatMap (lexEsc1 (vxv : vxw)) table); lexEsc4 vxv vxw False = lexEsc3 (vxv : vxw); ; lexEsc5 vxv vxw True = span isDigit (vxv : vxw) : []; lexEsc5 vxv vxw False = lexEsc4 vxv vxw (isUpper vxv); ; lexEsc6 (vxv : vxw) = lexEsc5 vxv vxw (isDigit vxv); lexEsc6 vuzv = lexEsc3 vuzv; ; lexEsc7 True (vuzx : s) = prefix 'x' (span isHexDigit s) : []; lexEsc7 vuzy vuzz = lexEsc6 vuzz; ; lexEsc8 (vuzx : s) = lexEsc7 (vuzx == 'x') (vuzx : s); lexEsc8 vvuu = lexEsc6 vvuu; ; lexEsc9 True (vvuw : s) = prefix 'o' (span isOctDigit s) : []; lexEsc9 vvux vvuy = lexEsc8 vvuy; ; lexLitChar0 c s True = map (prefix '\') (lexEsc s); ; lexLitChar1 c s True = (c : [],s) : []; lexLitChar1 c s False = lexLitChar0 c s otherwise; ; prefix c (t,s) = (c : t,s); ; table = ('\127','D' : 'E' : 'L' : []) : asciiTab; } ; " "lexLitChar3 [] = []; lexLitChar3 vvxu = lexLitChar2 vvxu; " The following Function with conditions "span p [] = ([],[]); span p (vyv : vyw)|p vyv(vyv : ys,zs)|otherwise([],vyv : vyw) where { vu43 = span p vyw; ; ys = ys0 vu43; ; ys0 (ys,vyy) = ys; ; zs = zs0 vu43; ; zs0 (vyx,zs) = zs; } ; " is transformed to "span p [] = span3 p []; span p (vyv : vyw) = span2 p (vyv : vyw); " "span2 p (vyv : vyw) = span1 p vyv vyw (p vyv) where { span0 p vyv vyw True = ([],vyv : vyw); ; span1 p vyv vyw True = (vyv : ys,zs); span1 p vyv vyw False = span0 p vyv vyw otherwise; ; vu43 = span p vyw; ; ys = ys0 vu43; ; ys0 (ys,vyy) = ys; ; zs = zs0 vu43; ; zs0 (vyx,zs) = zs; } ; " "span3 p [] = ([],[]); span3 vvxx vvxy = span2 vvxx vvxy; " ---------------------------------------- (10) Obligation: mainModule Main module Main where { import qualified Prelude; } ---------------------------------------- (11) LetRed (EQUIVALENT) Let/Where Reductions: The bindings of the following Let/Where expression "lexLitChar1 c s (c /= '\') where { lexEsc (c : s) = lexEsc16 (c : s); lexEsc (vvvv : vvvy) = lexEsc14 (vvvv : vvvy); lexEsc (vvuw : s) = lexEsc11 (vvuw : s); lexEsc (vuzx : s) = lexEsc8 (vuzx : s); lexEsc (vxv : vxw) = lexEsc6 (vxv : vxw); lexEsc vxx = lexEsc3 vxx; ; lexEsc0 mne vu69 = lexEsc00 mne vu69; ; lexEsc00 mne ([],s') = (mne,s') : []; lexEsc00 mne vxz = []; ; lexEsc1 s vu70 = lexEsc10 s vu70; ; lexEsc10 s (c,mne) = concatMap (lexEsc0 mne) (lexmatch mne s : []); lexEsc10 s vyu = []; ; lexEsc11 (vvuw : s) = lexEsc9 (vvuw == 'o') (vvuw : s); lexEsc11 vvuz = lexEsc8 vvuz; ; lexEsc12 vvvv c s True = ('^' : c : [],s) : []; lexEsc12 vvvv c s False = lexEsc11 (vvvv : c : s); ; lexEsc13 True (vvvv : c : s) = lexEsc12 vvvv c s (c >= '@' && c <= '_'); lexEsc13 vvvz vvwu = lexEsc11 vvwu; ; lexEsc14 (vvvv : vvvy) = lexEsc13 (vvvv == '^') (vvvv : vvvy); lexEsc14 vvwv = lexEsc11 vvwv; ; lexEsc15 c s True = (c : [],s) : []; lexEsc15 c s False = lexEsc14 (c : s); ; lexEsc16 (c : s) = lexEsc15 c s (c `elem` 'a' : 'b' : 'f' : 'n' : 'r' : 't' : 'v' : '\' : '"' : ''' : []); lexEsc16 vvwx = lexEsc14 vvwx; ; lexEsc2 (pr : vxy) = pr : []; lexEsc2 [] = []; ; lexEsc3 vxx = []; ; lexEsc4 vxv vxw True = lexEsc2 (concatMap (lexEsc1 (vxv : vxw)) table); lexEsc4 vxv vxw False = lexEsc3 (vxv : vxw); ; lexEsc5 vxv vxw True = span isDigit (vxv : vxw) : []; lexEsc5 vxv vxw False = lexEsc4 vxv vxw (isUpper vxv); ; lexEsc6 (vxv : vxw) = lexEsc5 vxv vxw (isDigit vxv); lexEsc6 vuzv = lexEsc3 vuzv; ; lexEsc7 True (vuzx : s) = prefix 'x' (span isHexDigit s) : []; lexEsc7 vuzy vuzz = lexEsc6 vuzz; ; lexEsc8 (vuzx : s) = lexEsc7 (vuzx == 'x') (vuzx : s); lexEsc8 vvuu = lexEsc6 vvuu; ; lexEsc9 True (vvuw : s) = prefix 'o' (span isOctDigit s) : []; lexEsc9 vvux vvuy = lexEsc8 vvuy; ; lexLitChar0 c s True = map (prefix '\') (lexEsc s); ; lexLitChar1 c s True = (c : [],s) : []; lexLitChar1 c s False = lexLitChar0 c s otherwise; ; prefix c (t,s) = (c : t,s); ; table = ('\127','D' : 'E' : 'L' : []) : asciiTab; } " are unpacked to the following functions on top level "lexLitChar2LexEsc (c : s) = lexLitChar2LexEsc16 (c : s); lexLitChar2LexEsc (vvvv : vvvy) = lexLitChar2LexEsc14 (vvvv : vvvy); lexLitChar2LexEsc (vvuw : s) = lexLitChar2LexEsc11 (vvuw : s); lexLitChar2LexEsc (vuzx : s) = lexLitChar2LexEsc8 (vuzx : s); lexLitChar2LexEsc (vxv : vxw) = lexLitChar2LexEsc6 (vxv : vxw); lexLitChar2LexEsc vxx = lexLitChar2LexEsc3 vxx; " "lexLitChar2LexEsc6 (vxv : vxw) = lexLitChar2LexEsc5 vxv vxw (isDigit vxv); lexLitChar2LexEsc6 vuzv = lexLitChar2LexEsc3 vuzv; " "lexLitChar2LexEsc14 (vvvv : vvvy) = lexLitChar2LexEsc13 (vvvv == '^') (vvvv : vvvy); lexLitChar2LexEsc14 vvwv = lexLitChar2LexEsc11 vvwv; " "lexLitChar2Prefix c (t,s) = (c : t,s); " "lexLitChar2LexEsc4 vxv vxw True = lexLitChar2LexEsc2 (concatMap (lexLitChar2LexEsc1 (vxv : vxw)) lexLitChar2Table); lexLitChar2LexEsc4 vxv vxw False = lexLitChar2LexEsc3 (vxv : vxw); " "lexLitChar2LexEsc5 vxv vxw True = span isDigit (vxv : vxw) : []; lexLitChar2LexEsc5 vxv vxw False = lexLitChar2LexEsc4 vxv vxw (isUpper vxv); " "lexLitChar2LexEsc16 (c : s) = lexLitChar2LexEsc15 c s (c `elem` 'a' : 'b' : 'f' : 'n' : 'r' : 't' : 'v' : '\' : '"' : ''' : []); lexLitChar2LexEsc16 vvwx = lexLitChar2LexEsc14 vvwx; " "lexLitChar2LexLitChar1 c s True = (c : [],s) : []; lexLitChar2LexLitChar1 c s False = lexLitChar2LexLitChar0 c s otherwise; " "lexLitChar2Table = ('\127','D' : 'E' : 'L' : []) : asciiTab; " "lexLitChar2LexEsc00 mne ([],s') = (mne,s') : []; lexLitChar2LexEsc00 mne vxz = []; " "lexLitChar2LexEsc3 vxx = []; " "lexLitChar2LexEsc15 c s True = (c : [],s) : []; lexLitChar2LexEsc15 c s False = lexLitChar2LexEsc14 (c : s); " "lexLitChar2LexEsc8 (vuzx : s) = lexLitChar2LexEsc7 (vuzx == 'x') (vuzx : s); lexLitChar2LexEsc8 vvuu = lexLitChar2LexEsc6 vvuu; " "lexLitChar2LexEsc7 True (vuzx : s) = lexLitChar2Prefix 'x' (span isHexDigit s) : []; lexLitChar2LexEsc7 vuzy vuzz = lexLitChar2LexEsc6 vuzz; " "lexLitChar2LexEsc2 (pr : vxy) = pr : []; lexLitChar2LexEsc2 [] = []; " "lexLitChar2LexEsc12 vvvv c s True = ('^' : c : [],s) : []; lexLitChar2LexEsc12 vvvv c s False = lexLitChar2LexEsc11 (vvvv : c : s); " "lexLitChar2LexEsc13 True (vvvv : c : s) = lexLitChar2LexEsc12 vvvv c s (c >= '@' && c <= '_'); lexLitChar2LexEsc13 vvvz vvwu = lexLitChar2LexEsc11 vvwu; " "lexLitChar2LexEsc0 mne vu69 = lexLitChar2LexEsc00 mne vu69; " "lexLitChar2LexLitChar0 c s True = map (lexLitChar2Prefix '\') (lexLitChar2LexEsc s); " "lexLitChar2LexEsc11 (vvuw : s) = lexLitChar2LexEsc9 (vvuw == 'o') (vvuw : s); lexLitChar2LexEsc11 vvuz = lexLitChar2LexEsc8 vvuz; " "lexLitChar2LexEsc1 s vu70 = lexLitChar2LexEsc10 s vu70; " "lexLitChar2LexEsc10 s (c,mne) = concatMap (lexLitChar2LexEsc0 mne) (lexmatch mne s : []); lexLitChar2LexEsc10 s vyu = []; " "lexLitChar2LexEsc9 True (vvuw : s) = lexLitChar2Prefix 'o' (span isOctDigit s) : []; lexLitChar2LexEsc9 vvux vvuy = lexLitChar2LexEsc8 vvuy; " The bindings of the following Let/Where expression "concatMap lex1 (lexString s) where { lex1 vu55 = lex10 vu55; ; lex10 (str,t) = ('"' : str,t) : []; lex10 xv = []; ; lexStrItem (wxw : wyu) = lexStrItem7 (wxw : wyu); lexStrItem (wwu : wwx) = lexStrItem4 (wwu : wwx); lexStrItem s = lexStrItem1 s; ; lexStrItem0 vu58 = lexStrItem00 vu58; ; lexStrItem00 (wzv : t) = lexStrItem002 (wzv : t); lexStrItem00 xu = lexStrItem000 xu; ; lexStrItem000 xu = []; ; lexStrItem001 True (wzv : t) = ([],t) : []; lexStrItem001 wzw wzx = lexStrItem000 wzx; ; lexStrItem002 (wzv : t) = lexStrItem001 (wzv == '\') (wzv : t); lexStrItem002 wzy = lexStrItem000 wzy; ; lexStrItem1 s = lexLitChar s; ; lexStrItem2 wwu c s True = concatMap lexStrItem0 (dropWhile isSpace s : []); lexStrItem2 wwu c s False = lexStrItem1 (wwu : c : s); ; lexStrItem3 True (wwu : c : s) = lexStrItem2 wwu c s (isSpace c); lexStrItem3 wwy wwz = lexStrItem1 wwz; ; lexStrItem4 (wwu : wwx) = lexStrItem3 (wwu == '\') (wwu : wwx); lexStrItem4 wxu = lexStrItem1 wxu; ; lexStrItem5 True (wxw : wxy : s) = ('\' : '&' : [],s) : []; lexStrItem5 wyv wyw = lexStrItem4 wyw; ; lexStrItem6 True (wxw : wxy : s) = lexStrItem5 (wxy == '&') (wxw : wxy : s); lexStrItem6 wyx wyy = lexStrItem4 wyy; ; lexStrItem7 (wxw : wyu) = lexStrItem6 (wxw == '\') (wxw : wyu); lexStrItem7 wyz = lexStrItem4 wyz; ; lexString (wvv : s) = lexString4 (wvv : s); lexString s = lexString2 s; ; lexString0 ch vu56 = lexString00 ch vu56; ; lexString00 ch (str,u) = (ch ++ str,u) : []; lexString00 ch wy = []; ; lexString1 vu57 = lexString10 vu57; ; lexString10 (ch,t) = concatMap (lexString0 ch) (lexString t); lexString10 wz = []; ; lexString2 s = concatMap lexString1 (lexStrItem s); ; lexString3 True (wvv : s) = ('"' : [],s) : []; lexString3 wvw wvx = lexString2 wvx; ; lexString4 (wvv : s) = lexString3 (wvv == '"') (wvv : s); lexString4 wvy = lexString2 wvy; } " are unpacked to the following functions on top level "lex13LexStrItem5 True (wxw : wxy : s) = ('\' : '&' : [],s) : []; lex13LexStrItem5 wyv wyw = lex13LexStrItem4 wyw; " "lex13LexString3 True (wvv : s) = ('"' : [],s) : []; lex13LexString3 wvw wvx = lex13LexString2 wvx; " "lex13LexStrItem00 (wzv : t) = lex13LexStrItem002 (wzv : t); lex13LexStrItem00 xu = lex13LexStrItem000 xu; " "lex13LexStrItem4 (wwu : wwx) = lex13LexStrItem3 (wwu == '\') (wwu : wwx); lex13LexStrItem4 wxu = lex13LexStrItem1 wxu; " "lex13Lex10 (str,t) = ('"' : str,t) : []; lex13Lex10 xv = []; " "lex13Lex1 vu55 = lex13Lex10 vu55; " "lex13LexStrItem000 xu = []; " "lex13LexStrItem1 s = lexLitChar s; " "lex13LexString1 vu57 = lex13LexString10 vu57; " "lex13LexString (wvv : s) = lex13LexString4 (wvv : s); lex13LexString s = lex13LexString2 s; " "lex13LexStrItem001 True (wzv : t) = ([],t) : []; lex13LexStrItem001 wzw wzx = lex13LexStrItem000 wzx; " "lex13LexString4 (wvv : s) = lex13LexString3 (wvv == '"') (wvv : s); lex13LexString4 wvy = lex13LexString2 wvy; " "lex13LexStrItem6 True (wxw : wxy : s) = lex13LexStrItem5 (wxy == '&') (wxw : wxy : s); lex13LexStrItem6 wyx wyy = lex13LexStrItem4 wyy; " "lex13LexStrItem7 (wxw : wyu) = lex13LexStrItem6 (wxw == '\') (wxw : wyu); lex13LexStrItem7 wyz = lex13LexStrItem4 wyz; " "lex13LexStrItem2 wwu c s True = concatMap lex13LexStrItem0 (dropWhile isSpace s : []); lex13LexStrItem2 wwu c s False = lex13LexStrItem1 (wwu : c : s); " "lex13LexString2 s = concatMap lex13LexString1 (lex13LexStrItem s); " "lex13LexString00 ch (str,u) = (ch ++ str,u) : []; lex13LexString00 ch wy = []; " "lex13LexString0 ch vu56 = lex13LexString00 ch vu56; " "lex13LexStrItem0 vu58 = lex13LexStrItem00 vu58; " "lex13LexStrItem (wxw : wyu) = lex13LexStrItem7 (wxw : wyu); lex13LexStrItem (wwu : wwx) = lex13LexStrItem4 (wwu : wwx); lex13LexStrItem s = lex13LexStrItem1 s; " "lex13LexString10 (ch,t) = concatMap (lex13LexString0 ch) (lex13LexString t); lex13LexString10 wz = []; " "lex13LexStrItem3 True (wwu : c : s) = lex13LexStrItem2 wwu c s (isSpace c); lex13LexStrItem3 wwy wwz = lex13LexStrItem1 wwz; " "lex13LexStrItem002 (wzv : t) = lex13LexStrItem001 (wzv == '\') (wzv : t); lex13LexStrItem002 wzy = lex13LexStrItem000 wzy; " The bindings of the following Let/Where expression "span1 p vyv vyw (p vyv) where { span0 p vyv vyw True = ([],vyv : vyw); ; span1 p vyv vyw True = (vyv : ys,zs); span1 p vyv vyw False = span0 p vyv vyw otherwise; ; vu43 = span p vyw; ; ys = ys0 vu43; ; ys0 (ys,vyy) = ys; ; zs = zs0 vu43; ; zs0 (vyx,zs) = zs; } " are unpacked to the following functions on top level "span2Ys0 vvxz vvyu (ys,vyy) = ys; " "span2Zs vvxz vvyu = span2Zs0 vvxz vvyu (span2Vu43 vvxz vvyu); " "span2Zs0 vvxz vvyu (vyx,zs) = zs; " "span2Vu43 vvxz vvyu = span vvxz vvyu; " "span2Span1 vvxz vvyu p vyv vyw True = (vyv : span2Ys vvxz vvyu,span2Zs vvxz vvyu); span2Span1 vvxz vvyu p vyv vyw False = span2Span0 vvxz vvyu p vyv vyw otherwise; " "span2Span0 vvxz vvyu p vyv vyw True = ([],vyv : vyw); " "span2Ys vvxz vvyu = span2Ys0 vvxz vvyu (span2Vu43 vvxz vvyu); " The bindings of the following Let/Where expression "lex11 c s (isSingle c) where { isIdChar c = isAlphaNum c || c `elem` '_' : ''' : []; ; isSingle c = c `elem` ',' : ';' : '(' : ')' : '[' : ']' : '{' : '}' : '_' : '`' : []; ; isSym c = c `elem` '!' : '@' : '#' : '$' : '%' : '&' : '*' : '+' : '.' : '/' : '<' : '=' : '>' : '?' : '\' : '^' : '|' : ':' : '-' : '~' : []; ; lex11 c s True = (c : [],s) : []; lex11 c s False = lex9 c s (isSym c); ; lex2 c vu59 = lex20 c vu59; ; lex20 c (sym,t) = (c : sym,t) : []; lex20 c yx = []; ; lex3 c vu60 = lex30 c vu60; ; lex30 c (nam,t) = (c : nam,t) : []; lex30 c yy = []; ; lex4 c ds vu61 = lex40 c ds vu61; ; lex40 c ds (fe,t) = (c : ds ++ fe,t) : []; lex40 c ds yv = []; ; lex5 c vu62 = lex50 c vu62; ; lex50 c (ds,s) = concatMap (lex4 c ds) (lexFracExp s); lex50 c yw = []; ; lex6 c s True = []; ; lex7 c s True = concatMap (lex5 c) (span isDigit s : []); lex7 c s False = lex6 c s otherwise; ; lex8 c s True = concatMap (lex3 c) (span isIdChar s : []); lex8 c s False = lex7 c s (isDigit c); ; lex9 c s True = concatMap (lex2 c) (span isSym s : []); lex9 c s False = lex8 c s (isAlpha c); ; lexExp (e : s) = lexExp5 (e : s); lexExp s = lexExp3 s; ; lexExp0 e c vu65 = lexExp00 e c vu65; ; lexExp00 e c (ds,u) = (e : c : ds,u) : []; lexExp00 e c xw = []; ; lexExp1 e vu66 = lexExp10 e vu66; ; lexExp10 e (c : t) = lexExp100 e c t (c `elem` '+' : '-' : []); lexExp10 e xy = []; ; lexExp100 e c t True = concatMap (lexExp0 e c) (lexDigits t); lexExp100 e c t False = []; ; lexExp2 e vu67 = lexExp20 e vu67; ; lexExp20 e (ds,t) = (e : ds,t) : []; lexExp20 e xx = []; ; lexExp3 s = ([],s) : []; ; lexExp4 e s True = concatMap (lexExp1 e) (s : []) ++ concatMap (lexExp2 e) (lexDigits s); lexExp4 e s False = lexExp3 (e : s); ; lexExp5 (e : s) = lexExp4 e s (e `elem` 'e' : 'E' : []); lexExp5 xuu = lexExp3 xuu; ; lexFracExp (xuw : xuz) = lexFracExp5 (xuw : xuz); lexFracExp s = lexFracExp2 s; ; lexFracExp0 ds vu63 = lexFracExp00 ds vu63; ; lexFracExp00 ds (e,u) = ('.' : ds ++ e,u) : []; lexFracExp00 ds yu = []; ; lexFracExp1 vu64 = lexFracExp10 vu64; ; lexFracExp10 (ds,t) = concatMap (lexFracExp0 ds) (lexExp t); lexFracExp10 xz = []; ; lexFracExp2 s = lexExp s; ; lexFracExp3 xuw c cs True = concatMap lexFracExp1 (lexDigits (c : cs)); lexFracExp3 xuw c cs False = lexFracExp2 (xuw : c : cs); ; lexFracExp4 True (xuw : c : cs) = lexFracExp3 xuw c cs (isDigit c); lexFracExp4 xvu xvv = lexFracExp2 xvv; ; lexFracExp5 (xuw : xuz) = lexFracExp4 (xuw == '.') (xuw : xuz); lexFracExp5 xvw = lexFracExp2 xvw; } " are unpacked to the following functions on top level "lex12IsSingle c = c `elem` ',' : ';' : '(' : ')' : '[' : ']' : '{' : '}' : '_' : '`' : []; " "lex12LexExp2 e vu67 = lex12LexExp20 e vu67; " "lex12LexFracExp0 ds vu63 = lex12LexFracExp00 ds vu63; " "lex12LexExp100 e c t True = concatMap (lex12LexExp0 e c) (lexDigits t); lex12LexExp100 e c t False = []; " "lex12Lex11 c s True = (c : [],s) : []; lex12Lex11 c s False = lex12Lex9 c s (lex12IsSym c); " "lex12Lex2 c vu59 = lex12Lex20 c vu59; " "lex12Lex3 c vu60 = lex12Lex30 c vu60; " "lex12Lex50 c (ds,s) = concatMap (lex12Lex4 c ds) (lex12LexFracExp s); lex12Lex50 c yw = []; " "lex12LexFracExp (xuw : xuz) = lex12LexFracExp5 (xuw : xuz); lex12LexFracExp s = lex12LexFracExp2 s; " "lex12Lex4 c ds vu61 = lex12Lex40 c ds vu61; " "lex12Lex40 c ds (fe,t) = (c : ds ++ fe,t) : []; lex12Lex40 c ds yv = []; " "lex12LexExp20 e (ds,t) = (e : ds,t) : []; lex12LexExp20 e xx = []; " "lex12IsSym c = c `elem` '!' : '@' : '#' : '$' : '%' : '&' : '*' : '+' : '.' : '/' : '<' : '=' : '>' : '?' : '\' : '^' : '|' : ':' : '-' : '~' : []; " "lex12LexExp5 (e : s) = lex12LexExp4 e s (e `elem` 'e' : 'E' : []); lex12LexExp5 xuu = lex12LexExp3 xuu; " "lex12Lex9 c s True = concatMap (lex12Lex2 c) (span lex12IsSym s : []); lex12Lex9 c s False = lex12Lex8 c s (isAlpha c); " "lex12LexExp10 e (c : t) = lex12LexExp100 e c t (c `elem` '+' : '-' : []); lex12LexExp10 e xy = []; " "lex12LexFracExp10 (ds,t) = concatMap (lex12LexFracExp0 ds) (lex12LexExp t); lex12LexFracExp10 xz = []; " "lex12LexFracExp5 (xuw : xuz) = lex12LexFracExp4 (xuw == '.') (xuw : xuz); lex12LexFracExp5 xvw = lex12LexFracExp2 xvw; " "lex12LexFracExp1 vu64 = lex12LexFracExp10 vu64; " "lex12IsIdChar c = isAlphaNum c || c `elem` '_' : ''' : []; " "lex12LexExp00 e c (ds,u) = (e : c : ds,u) : []; lex12LexExp00 e c xw = []; " "lex12LexExp (e : s) = lex12LexExp5 (e : s); lex12LexExp s = lex12LexExp3 s; " "lex12LexExp0 e c vu65 = lex12LexExp00 e c vu65; " "lex12LexExp3 s = ([],s) : []; " "lex12Lex30 c (nam,t) = (c : nam,t) : []; lex12Lex30 c yy = []; " "lex12LexFracExp2 s = lex12LexExp s; " "lex12Lex6 c s True = []; " "lex12Lex8 c s True = concatMap (lex12Lex3 c) (span lex12IsIdChar s : []); lex12Lex8 c s False = lex12Lex7 c s (isDigit c); " "lex12LexFracExp3 xuw c cs True = concatMap lex12LexFracExp1 (lexDigits (c : cs)); lex12LexFracExp3 xuw c cs False = lex12LexFracExp2 (xuw : c : cs); " "lex12Lex20 c (sym,t) = (c : sym,t) : []; lex12Lex20 c yx = []; " "lex12Lex7 c s True = concatMap (lex12Lex5 c) (span isDigit s : []); lex12Lex7 c s False = lex12Lex6 c s otherwise; " "lex12LexFracExp4 True (xuw : c : cs) = lex12LexFracExp3 xuw c cs (isDigit c); lex12LexFracExp4 xvu xvv = lex12LexFracExp2 xvv; " "lex12LexFracExp00 ds (e,u) = ('.' : ds ++ e,u) : []; lex12LexFracExp00 ds yu = []; " "lex12LexExp4 e s True = concatMap (lex12LexExp1 e) (s : []) ++ concatMap (lex12LexExp2 e) (lexDigits s); lex12LexExp4 e s False = lex12LexExp3 (e : s); " "lex12Lex5 c vu62 = lex12Lex50 c vu62; " "lex12LexExp1 e vu66 = lex12LexExp10 e vu66; " The bindings of the following Let/Where expression "readInt 16 isHexDigit hex where { hex d = fromEnum d - hex1 d (isDigit d); ; hex0 True = 'A'; hex0 False = 'a'; ; hex1 d True = fromEnum_0; hex1 d False = fromEnum (hex0 (isUpper d)) - 10; } " are unpacked to the following functions on top level "readHexHex1 d True = fromEnum_0; readHexHex1 d False = fromEnum (readHexHex0 (isUpper d)) - 10; " "readHexHex0 True = 'A'; readHexHex0 False = 'a'; " "readHexHex d = fromEnum d - readHexHex1 d (isDigit d); " The bindings of the following Let/Where expression "readParen0 b where { mandatory r = concatMap mandatory2 (lex r); ; mandatory0 x vu48 = mandatory00 x vu48; ; mandatory00 x (vuwv : vuww,u) = mandatory002 x (vuwv : vuww,u); mandatory00 x vwv = mandatory000 x vwv; ; mandatory000 x vwv = []; ; mandatory001 True x (vuwv : [],u) = (x,u) : []; mandatory001 vuwx vuwy vuwz = mandatory000 vuwy vuwz; ; mandatory002 x (vuwv : vuww,u) = mandatory001 (vuwv == ')') x (vuwv : vuww,u); mandatory002 vuxu vuxv = mandatory000 vuxu vuxv; ; mandatory1 vu49 = mandatory10 vu49; ; mandatory10 (x,t) = concatMap (mandatory0 x) (lex t); mandatory10 vww = []; ; mandatory2 vu50 = mandatory20 vu50; ; mandatory20 (vuvu : vuvv,s) = mandatory202 (vuvu : vuvv,s); mandatory20 vwu = mandatory200 vwu; ; mandatory200 vwu = []; ; mandatory201 True (vuvu : [],s) = concatMap mandatory1 (optional s); mandatory201 vuvw vuvx = mandatory200 vuvx; ; mandatory202 (vuvu : vuvv,s) = mandatory201 (vuvu == '(') (vuvu : vuvv,s); mandatory202 vuvy = mandatory200 vuvy; ; optional r = g r ++ mandatory r; ; readParen0 True = mandatory; readParen0 False = optional; } " are unpacked to the following functions on top level "readParenMandatory002 vvyv x (vuwv : vuww,u) = readParenMandatory001 vvyv (vuwv == ')') x (vuwv : vuww,u); readParenMandatory002 vvyv vuxu vuxv = readParenMandatory000 vvyv vuxu vuxv; " "readParenOptional vvyv r = vvyv r ++ readParenMandatory vvyv r; " "readParenMandatory201 vvyv True (vuvu : [],s) = concatMap (readParenMandatory1 vvyv) (readParenOptional vvyv s); readParenMandatory201 vvyv vuvw vuvx = readParenMandatory200 vvyv vuvx; " "readParenMandatory202 vvyv (vuvu : vuvv,s) = readParenMandatory201 vvyv (vuvu == '(') (vuvu : vuvv,s); readParenMandatory202 vvyv vuvy = readParenMandatory200 vvyv vuvy; " "readParenMandatory2 vvyv vu50 = readParenMandatory20 vvyv vu50; " "readParenMandatory200 vvyv vwu = []; " "readParenMandatory001 vvyv True x (vuwv : [],u) = (x,u) : []; readParenMandatory001 vvyv vuwx vuwy vuwz = readParenMandatory000 vvyv vuwy vuwz; " "readParenMandatory10 vvyv (x,t) = concatMap (readParenMandatory0 vvyv x) (lex t); readParenMandatory10 vvyv vww = []; " "readParenMandatory00 vvyv x (vuwv : vuww,u) = readParenMandatory002 vvyv x (vuwv : vuww,u); readParenMandatory00 vvyv x vwv = readParenMandatory000 vvyv x vwv; " "readParenMandatory vvyv r = concatMap (readParenMandatory2 vvyv) (lex r); " "readParenMandatory000 vvyv x vwv = []; " "readParenMandatory0 vvyv x vu48 = readParenMandatory00 vvyv x vu48; " "readParenReadParen0 vvyv True = readParenMandatory vvyv; readParenReadParen0 vvyv False = readParenOptional vvyv; " "readParenMandatory1 vvyv vu49 = readParenMandatory10 vvyv vu49; " "readParenMandatory20 vvyv (vuvu : vuvv,s) = readParenMandatory202 vvyv (vuvu : vuvv,s); readParenMandatory20 vvyv vwu = readParenMandatory200 vvyv vwu; " The bindings of the following Let/Where expression "readEsc s where { readEsc (zyw : s) = readEsc41 (zyw : s); readEsc (zxx : s) = readEsc38 (zxx : s); readEsc (zwy : s) = readEsc36 (zwy : s); readEsc (zvz : s) = readEsc34 (zvz : s); readEsc (zvu : s) = readEsc32 (zvu : s); readEsc (zuv : s) = readEsc29 (zuv : s); readEsc (yzw : s) = readEsc27 (yzw : s); readEsc (yyx : s) = readEsc25 (yyx : s); readEsc (yxy : s) = readEsc23 (yxy : s); readEsc (ywz : s) = readEsc21 (ywz : s); readEsc (yvx : ywu) = readEsc18 (yvx : ywu); readEsc (zv : zw) = readEsc15 (zv : zw); readEsc (yuw : s) = readEsc13 (yuw : s); readEsc (xzx : s) = readEsc11 (xzx : s); readEsc (zy : zz) = readEsc8 (zy : zz); readEsc vux = readEsc6 vux; ; readEsc0 vu71 = readEsc00 vu71; ; readEsc00 (n,t) = (toEnum n,t) : []; readEsc00 vuy = []; ; readEsc1 vu72 = readEsc10 vu72; ; readEsc10 (n,t) = (toEnum n,t) : []; readEsc10 vuz = []; ; readEsc11 (xzx : s) = readEsc9 (xzx == 'x') (xzx : s); readEsc11 yuu = readEsc8 yuu; ; readEsc12 True (yuw : s) = concatMap readEsc1 (readOct s); readEsc12 yux yuy = readEsc11 yuy; ; readEsc13 (yuw : s) = readEsc12 (yuw == 'o') (yuw : s); readEsc13 yuz = readEsc11 yuz; ; readEsc14 zv zw True = concatMap readEsc0 (readDec (zv : zw)); readEsc14 zv zw False = readEsc13 (zv : zw); ; readEsc15 (zv : zw) = readEsc14 zv zw (isDigit zv); readEsc15 yvv = readEsc13 yvv; ; readEsc16 yvx c s True = (toEnum (fromEnum c - fromEnum '@'),s) : []; readEsc16 yvx c s False = readEsc15 (yvx : c : s); ; readEsc17 True (yvx : c : s) = readEsc16 yvx c s (c >= '@' && c <= '_'); readEsc17 ywv yww = readEsc15 yww; ; readEsc18 (yvx : ywu) = readEsc17 (yvx == '^') (yvx : ywu); readEsc18 ywx = readEsc15 ywx; ; readEsc19 True (ywz : s) = (''',s) : []; readEsc19 yxu yxv = readEsc18 yxv; ; readEsc2 vu73 = readEsc20 vu73; ; readEsc20 (n,t) = (toEnum n,t) : []; readEsc20 vvu = []; ; readEsc21 (ywz : s) = readEsc19 (ywz == ''') (ywz : s); readEsc21 yxw = readEsc18 yxw; ; readEsc22 True (yxy : s) = ('"',s) : []; readEsc22 yxz yyu = readEsc21 yyu; ; readEsc23 (yxy : s) = readEsc22 (yxy == '"') (yxy : s); readEsc23 yyv = readEsc21 yyv; ; readEsc24 True (yyx : s) = ('\',s) : []; readEsc24 yyy yyz = readEsc23 yyz; ; readEsc25 (yyx : s) = readEsc24 (yyx == '\') (yyx : s); readEsc25 yzu = readEsc23 yzu; ; readEsc26 True (yzw : s) = ('\11',s) : []; readEsc26 yzx yzy = readEsc25 yzy; ; readEsc27 (yzw : s) = readEsc26 (yzw == 'v') (yzw : s); readEsc27 yzz = readEsc25 yzz; ; readEsc28 True (zuv : s) = ('\9',s) : []; readEsc28 zuw zux = readEsc27 zux; ; readEsc29 (zuv : s) = readEsc28 (zuv == 't') (zuv : s); readEsc29 zuy = readEsc27 zuy; ; readEsc31 True (zvu : s) = ('\13',s) : []; readEsc31 zvv zvw = readEsc29 zvw; ; readEsc32 (zvu : s) = readEsc31 (zvu == 'r') (zvu : s); readEsc32 zvx = readEsc29 zvx; ; readEsc33 True (zvz : s) = ('\10',s) : []; readEsc33 zwu zwv = readEsc32 zwv; ; readEsc34 (zvz : s) = readEsc33 (zvz == 'n') (zvz : s); readEsc34 zww = readEsc32 zww; ; readEsc35 True (zwy : s) = ('\12',s) : []; readEsc35 zwz zxu = readEsc34 zxu; ; readEsc36 (zwy : s) = readEsc35 (zwy == 'f') (zwy : s); readEsc36 zxv = readEsc34 zxv; ; readEsc37 True (zxx : s) = ('\8',s) : []; readEsc37 zxy zxz = readEsc36 zxz; ; readEsc38 (zxx : s) = readEsc37 (zxx == 'b') (zxx : s); readEsc38 zyu = readEsc36 zyu; ; readEsc39 True (zyw : s) = ('\7',s) : []; readEsc39 zyx zyy = readEsc38 zyy; ; readEsc41 (zyw : s) = readEsc39 (zyw == 'a') (zyw : s); readEsc41 zyz = readEsc38 zyz; ; readEsc6 vux = []; ; readEsc7 zy zz True = let { readEsc3 c vu74 = readEsc30 c vu74; ; readEsc30 c ([],s') = (c,s') : []; readEsc30 c vuw = []; ; readEsc4 s vu75 = readEsc40 s vu75; ; readEsc40 s (c,mne) = concatMap (readEsc3 c) (lexmatch mne s : []); readEsc40 s vuv = []; ; readEsc5 (pr : vuu) = pr : []; readEsc5 [] = []; ; table = ('\127','D' : 'E' : 'L' : []) : asciiTab; } in readEsc5 (concatMap (readEsc4 (zy : zz)) table); readEsc7 zy zz False = readEsc6 (zy : zz); ; readEsc8 (zy : zz) = readEsc7 zy zz (isUpper zy); readEsc8 xzv = readEsc6 xzv; ; readEsc9 True (xzx : s) = concatMap readEsc2 (readHex s); readEsc9 xzy xzz = readEsc8 xzz; } " are unpacked to the following functions on top level "readLitChar1ReadEsc12 True (yuw : s) = concatMap readLitChar1ReadEsc1 (readOct s); readLitChar1ReadEsc12 yux yuy = readLitChar1ReadEsc11 yuy; " "readLitChar1ReadEsc41 (zyw : s) = readLitChar1ReadEsc39 (zyw == 'a') (zyw : s); readLitChar1ReadEsc41 zyz = readLitChar1ReadEsc38 zyz; " "readLitChar1ReadEsc37 True (zxx : s) = ('\8',s) : []; readLitChar1ReadEsc37 zxy zxz = readLitChar1ReadEsc36 zxz; " "readLitChar1ReadEsc25 (yyx : s) = readLitChar1ReadEsc24 (yyx == '\') (yyx : s); readLitChar1ReadEsc25 yzu = readLitChar1ReadEsc23 yzu; " "readLitChar1ReadEsc33 True (zvz : s) = ('\10',s) : []; readLitChar1ReadEsc33 zwu zwv = readLitChar1ReadEsc32 zwv; " "readLitChar1ReadEsc (zyw : s) = readLitChar1ReadEsc41 (zyw : s); readLitChar1ReadEsc (zxx : s) = readLitChar1ReadEsc38 (zxx : s); readLitChar1ReadEsc (zwy : s) = readLitChar1ReadEsc36 (zwy : s); readLitChar1ReadEsc (zvz : s) = readLitChar1ReadEsc34 (zvz : s); readLitChar1ReadEsc (zvu : s) = readLitChar1ReadEsc32 (zvu : s); readLitChar1ReadEsc (zuv : s) = readLitChar1ReadEsc29 (zuv : s); readLitChar1ReadEsc (yzw : s) = readLitChar1ReadEsc27 (yzw : s); readLitChar1ReadEsc (yyx : s) = readLitChar1ReadEsc25 (yyx : s); readLitChar1ReadEsc (yxy : s) = readLitChar1ReadEsc23 (yxy : s); readLitChar1ReadEsc (ywz : s) = readLitChar1ReadEsc21 (ywz : s); readLitChar1ReadEsc (yvx : ywu) = readLitChar1ReadEsc18 (yvx : ywu); readLitChar1ReadEsc (zv : zw) = readLitChar1ReadEsc15 (zv : zw); readLitChar1ReadEsc (yuw : s) = readLitChar1ReadEsc13 (yuw : s); readLitChar1ReadEsc (xzx : s) = readLitChar1ReadEsc11 (xzx : s); readLitChar1ReadEsc (zy : zz) = readLitChar1ReadEsc8 (zy : zz); readLitChar1ReadEsc vux = readLitChar1ReadEsc6 vux; " "readLitChar1ReadEsc10 (n,t) = (toEnum n,t) : []; readLitChar1ReadEsc10 vuz = []; " "readLitChar1ReadEsc32 (zvu : s) = readLitChar1ReadEsc31 (zvu == 'r') (zvu : s); readLitChar1ReadEsc32 zvx = readLitChar1ReadEsc29 zvx; " "readLitChar1ReadEsc39 True (zyw : s) = ('\7',s) : []; readLitChar1ReadEsc39 zyx zyy = readLitChar1ReadEsc38 zyy; " "readLitChar1ReadEsc17 True (yvx : c : s) = readLitChar1ReadEsc16 yvx c s (c >= '@' && c <= '_'); readLitChar1ReadEsc17 ywv yww = readLitChar1ReadEsc15 yww; " "readLitChar1ReadEsc23 (yxy : s) = readLitChar1ReadEsc22 (yxy == '"') (yxy : s); readLitChar1ReadEsc23 yyv = readLitChar1ReadEsc21 yyv; " "readLitChar1ReadEsc34 (zvz : s) = readLitChar1ReadEsc33 (zvz == 'n') (zvz : s); readLitChar1ReadEsc34 zww = readLitChar1ReadEsc32 zww; " "readLitChar1ReadEsc00 (n,t) = (toEnum n,t) : []; readLitChar1ReadEsc00 vuy = []; " "readLitChar1ReadEsc2 vu73 = readLitChar1ReadEsc20 vu73; " "readLitChar1ReadEsc9 True (xzx : s) = concatMap readLitChar1ReadEsc2 (readHex s); readLitChar1ReadEsc9 xzy xzz = readLitChar1ReadEsc8 xzz; " "readLitChar1ReadEsc8 (zy : zz) = readLitChar1ReadEsc7 zy zz (isUpper zy); readLitChar1ReadEsc8 xzv = readLitChar1ReadEsc6 xzv; " "readLitChar1ReadEsc31 True (zvu : s) = ('\13',s) : []; readLitChar1ReadEsc31 zvv zvw = readLitChar1ReadEsc29 zvw; " "readLitChar1ReadEsc27 (yzw : s) = readLitChar1ReadEsc26 (yzw == 'v') (yzw : s); readLitChar1ReadEsc27 yzz = readLitChar1ReadEsc25 yzz; " "readLitChar1ReadEsc14 zv zw True = concatMap readLitChar1ReadEsc0 (readDec (zv : zw)); readLitChar1ReadEsc14 zv zw False = readLitChar1ReadEsc13 (zv : zw); " "readLitChar1ReadEsc29 (zuv : s) = readLitChar1ReadEsc28 (zuv == 't') (zuv : s); readLitChar1ReadEsc29 zuy = readLitChar1ReadEsc27 zuy; " "readLitChar1ReadEsc19 True (ywz : s) = (''',s) : []; readLitChar1ReadEsc19 yxu yxv = readLitChar1ReadEsc18 yxv; " "readLitChar1ReadEsc35 True (zwy : s) = ('\12',s) : []; readLitChar1ReadEsc35 zwz zxu = readLitChar1ReadEsc34 zxu; " "readLitChar1ReadEsc22 True (yxy : s) = ('"',s) : []; readLitChar1ReadEsc22 yxz yyu = readLitChar1ReadEsc21 yyu; " "readLitChar1ReadEsc15 (zv : zw) = readLitChar1ReadEsc14 zv zw (isDigit zv); readLitChar1ReadEsc15 yvv = readLitChar1ReadEsc13 yvv; " "readLitChar1ReadEsc6 vux = []; " "readLitChar1ReadEsc13 (yuw : s) = readLitChar1ReadEsc12 (yuw == 'o') (yuw : s); readLitChar1ReadEsc13 yuz = readLitChar1ReadEsc11 yuz; " "readLitChar1ReadEsc26 True (yzw : s) = ('\11',s) : []; readLitChar1ReadEsc26 yzx yzy = readLitChar1ReadEsc25 yzy; " "readLitChar1ReadEsc21 (ywz : s) = readLitChar1ReadEsc19 (ywz == ''') (ywz : s); readLitChar1ReadEsc21 yxw = readLitChar1ReadEsc18 yxw; " "readLitChar1ReadEsc0 vu71 = readLitChar1ReadEsc00 vu71; " "readLitChar1ReadEsc24 True (yyx : s) = ('\',s) : []; readLitChar1ReadEsc24 yyy yyz = readLitChar1ReadEsc23 yyz; " "readLitChar1ReadEsc7 zy zz True = readLitChar1ReadEsc7ReadEsc5 (concatMap (readLitChar1ReadEsc7ReadEsc4 (zy : zz)) readLitChar1ReadEsc7Table); readLitChar1ReadEsc7 zy zz False = readLitChar1ReadEsc6 (zy : zz); " "readLitChar1ReadEsc28 True (zuv : s) = ('\9',s) : []; readLitChar1ReadEsc28 zuw zux = readLitChar1ReadEsc27 zux; " "readLitChar1ReadEsc38 (zxx : s) = readLitChar1ReadEsc37 (zxx == 'b') (zxx : s); readLitChar1ReadEsc38 zyu = readLitChar1ReadEsc36 zyu; " "readLitChar1ReadEsc18 (yvx : ywu) = readLitChar1ReadEsc17 (yvx == '^') (yvx : ywu); readLitChar1ReadEsc18 ywx = readLitChar1ReadEsc15 ywx; " "readLitChar1ReadEsc11 (xzx : s) = readLitChar1ReadEsc9 (xzx == 'x') (xzx : s); readLitChar1ReadEsc11 yuu = readLitChar1ReadEsc8 yuu; " "readLitChar1ReadEsc20 (n,t) = (toEnum n,t) : []; readLitChar1ReadEsc20 vvu = []; " "readLitChar1ReadEsc1 vu72 = readLitChar1ReadEsc10 vu72; " "readLitChar1ReadEsc16 yvx c s True = (toEnum (fromEnum c - fromEnum '@'),s) : []; readLitChar1ReadEsc16 yvx c s False = readLitChar1ReadEsc15 (yvx : c : s); " "readLitChar1ReadEsc36 (zwy : s) = readLitChar1ReadEsc35 (zwy == 'f') (zwy : s); readLitChar1ReadEsc36 zxv = readLitChar1ReadEsc34 zxv; " The bindings of the following Let/Where expression "let { readEsc3 c vu74 = readEsc30 c vu74; ; readEsc30 c ([],s') = (c,s') : []; readEsc30 c vuw = []; ; readEsc4 s vu75 = readEsc40 s vu75; ; readEsc40 s (c,mne) = concatMap (readEsc3 c) (lexmatch mne s : []); readEsc40 s vuv = []; ; readEsc5 (pr : vuu) = pr : []; readEsc5 [] = []; ; table = ('\127','D' : 'E' : 'L' : []) : asciiTab; } in readEsc5 (concatMap (readEsc4 (zy : zz)) table)" are unpacked to the following functions on top level "readLitChar1ReadEsc7Table = ('\127','D' : 'E' : 'L' : []) : asciiTab; " "readLitChar1ReadEsc7ReadEsc4 s vu75 = readLitChar1ReadEsc7ReadEsc40 s vu75; " "readLitChar1ReadEsc7ReadEsc3 c vu74 = readLitChar1ReadEsc7ReadEsc30 c vu74; " "readLitChar1ReadEsc7ReadEsc5 (pr : vuu) = pr : []; readLitChar1ReadEsc7ReadEsc5 [] = []; " "readLitChar1ReadEsc7ReadEsc40 s (c,mne) = concatMap (readLitChar1ReadEsc7ReadEsc3 c) (lexmatch mne s : []); readLitChar1ReadEsc7ReadEsc40 s vuv = []; " "readLitChar1ReadEsc7ReadEsc30 c ([],s') = (c,s') : []; readLitChar1ReadEsc7ReadEsc30 c vuw = []; " ---------------------------------------- (12) Obligation: mainModule Main module Main where { import qualified Prelude; } ---------------------------------------- (13) NumRed (SOUND) Num Reduction:All numbers are transformed to their corresponding representation with Succ, Pred and Zero. ---------------------------------------- (14) Obligation: mainModule Main module Main where { import qualified Prelude; }