summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorPéter Diviánszky <divipp@gmail.com>2016-02-03 08:33:03 +0100
committerPéter Diviánszky <divipp@gmail.com>2016-02-03 08:33:03 +0100
commitf764568bc9c47069190475099cbe1dbe561f9fa4 (patch)
treefdeb49c17c9b7385e2e8d267e3a3e562f211c3cd
parent4584f989c6a306a7b433a38406403d9af042ca11 (diff)
refactor literal parsing
-rw-r--r--src/LambdaCube/Compiler/Lexer.hs345
-rw-r--r--src/LambdaCube/Compiler/Parser.hs50
-rw-r--r--testdata/Builtins.out20
-rw-r--r--testdata/language-features/basic-values/def05.reject.out2
-rw-r--r--testdata/language-features/basic-values/def06.reject.out2
-rw-r--r--testdata/language-features/basic-values/redefine03.reject.out2
-rw-r--r--testdata/language-features/guard/guard10.reject.out2
-rw-r--r--testdata/listcompr01.reject.out2
8 files changed, 202 insertions, 223 deletions
diff --git a/src/LambdaCube/Compiler/Lexer.hs b/src/LambdaCube/Compiler/Lexer.hs
index 576cba23..e3ef0333 100644
--- a/src/LambdaCube/Compiler/Lexer.hs
+++ b/src/LambdaCube/Compiler/Lexer.hs
@@ -64,6 +64,22 @@ namespace :: P Namespace
64namespace = asks snd 64namespace = asks snd
65 65
66 66
67-------------------------------------------------------------------------------- literals
68
69data Lit
70 = LInt Integer
71 | LChar Char
72 | LFloat Double
73 | LString String
74 deriving (Eq)
75
76instance Show Lit where
77 show = \case
78 LFloat x -> show x
79 LString x -> show x
80 LInt x -> show x
81 LChar x -> show x
82
67-------------------------------------------------------------------------------- names 83-------------------------------------------------------------------------------- names
68 84
69type SName = String 85type SName = String
@@ -278,7 +294,8 @@ parseFixityDecl = do
278 <|> InfixL <$ reserved "infixl" 294 <|> InfixL <$ reserved "infixl"
279 <|> InfixR <$ reserved "infixr" 295 <|> InfixR <$ reserved "infixr"
280 localIndentation Gt $ do 296 localIndentation Gt $ do
281 i <- fromIntegral <$> natural 297 LInt n <- parseLit
298 let i = fromIntegral n
282 ns <- commaSep1 (parseSIName rhsOperator) 299 ns <- commaSep1 (parseSIName rhsOperator)
283 return $ (,) <$> ns <*> pure (dir, i) 300 return $ (,) <$> ns <*> pure (dir, i)
284 301
@@ -313,182 +330,162 @@ semiSep p = sepBy p semi
313commaSep1 p = sepBy1 p comma 330commaSep1 p = sepBy1 p comma
314semiSep1 p = sepBy1 p semi 331semiSep1 p = sepBy1 p semi
315 332
316
317----------------------------------------------------------- 333-----------------------------------------------------------
318-- Chars & Strings
319-----------------------------------------------------------
320charLiteral = lexeme (between (char '\'')
321 (char '\'' <?> "end of character")
322 characterChar )
323 <?> "character"
324
325characterChar = charLetter <|> charEscape
326 <?> "literal character"
327
328charEscape = do{ char '\\'; escapeCode }
329charLetter = satisfy (\c -> (c /= '\'') && (c /= '\\') && (c > '\026'))
330
331
332
333stringLiteral = lexeme (
334 do{ str <- between (char '"')
335 (localTokenMode (const Pa.Any) (char '"' <?> "end of string"))
336 (localTokenMode (const Pa.Any) (many stringChar))
337 ; return (foldr (maybe id (:)) "" str)
338 }
339 <?> "literal string")
340
341stringChar = do{ c <- stringLetter; return (Just c) }
342 <|> stringEscape
343 <?> "string character"
344
345stringLetter = satisfy (\c -> (c /= '"') && (c /= '\\') && (c > '\026'))
346
347stringEscape = do{ char '\\'
348 ; do{ escapeGap ; return Nothing }
349 <|> do{ escapeEmpty; return Nothing }
350 <|> do{ esc <- escapeCode; return (Just esc) }
351 }
352
353escapeEmpty = char '&'
354escapeGap = do{ many1 space
355 ; char '\\' <?> "end of string gap"
356 }
357
358
359
360-- escape codes
361escapeCode = charEsc <|> charNum <|> charAscii <|> charControl
362 <?> "escape code"
363
364charControl = do{ char '^'
365 ; code <- upper
366 ; return (toEnum (fromEnum code - fromEnum 'A'))
367 }
368
369charNum = do{ code <- decimal
370 <|> do{ char 'o'; number 8 octDigit }
371 <|> do{ char 'x'; number 16 hexDigit }
372 ; return (toEnum (fromInteger code))
373 }
374
375charEsc = choice (map parseEsc escMap)
376 where
377 parseEsc (c,code) = do{ char c; return code }
378
379charAscii = choice (map parseAscii asciiMap)
380 where
381 parseAscii (asc,code) = try (do{ string asc; return code })
382
383
384-- escape code tables
385escMap = zip ("abfnrtv\\\"\'") ("\a\b\f\n\r\t\v\\\"\'")
386asciiMap = zip (ascii3codes ++ ascii2codes) (ascii3 ++ ascii2)
387
388ascii2codes = ["BS","HT","LF","VT","FF","CR","SO","SI","EM",
389 "FS","GS","RS","US","SP"]
390ascii3codes = ["NUL","SOH","STX","ETX","EOT","ENQ","ACK","BEL",
391 "DLE","DC1","DC2","DC3","DC4","NAK","SYN","ETB",
392 "CAN","SUB","ESC","DEL"]
393
394ascii2 = ['\BS','\HT','\LF','\VT','\FF','\CR','\SO','\SI',
395 '\EM','\FS','\GS','\RS','\US','\SP']
396ascii3 = ['\NUL','\SOH','\STX','\ETX','\EOT','\ENQ','\ACK',
397 '\BEL','\DLE','\DC1','\DC2','\DC3','\DC4','\NAK',
398 '\SYN','\ETB','\CAN','\SUB','\ESC','\DEL']
399 334
335parseLit = lexeme $ charLiteral <|> stringLiteral <|> natFloat
336 where
337 -----------------------------------------------------------
338 -- Chars & Strings
339 -----------------------------------------------------------
340 charLiteral = LChar <$> between (char '\'')
341 (char '\'' <?> "end of character")
342 characterChar
343 <?> "character"
344
345 characterChar = charLetter <|> charEscape
346 <?> "literal character"
400 347
401----------------------------------------------------------- 348 charEscape = do{ char '\\'; escapeCode }
402-- Numbers 349 charLetter = satisfy (\c -> (c /= '\'') && (c /= '\\') && (c > '\026'))
403----------------------------------------------------------- 350
404naturalOrFloat = lexeme (natFloat) <?> "number" 351
405 352
406float = lexeme floating <?> "float" 353 stringLiteral = LString <$>
407integer = lexeme int <?> "integer" 354 do{ str <- between (char '"')
408natural = lexeme nat <?> "natural" 355 (localTokenMode (const Pa.Any) (char '"' <?> "end of string"))
409 356 (localTokenMode (const Pa.Any) (many stringChar))
410 357 ; return (foldr (maybe id (:)) "" str)
411-- floats 358 }
412floating = do{ n <- decimal 359 <?> "literal string"
413 ; fractExponent n 360
414 } 361 stringChar = do{ c <- stringLetter; return (Just c) }
415 362 <|> stringEscape
416 363 <?> "string character"
417natFloat = do{ char '0' 364
418 ; zeroNumFloat 365 stringLetter = satisfy (\c -> (c /= '"') && (c /= '\\') && (c > '\026'))
419 } 366
420 <|> decimalFloat 367 stringEscape = do{ char '\\'
421 368 ; do{ escapeGap ; return Nothing }
422zeroNumFloat = do{ n <- hexadecimal <|> octal 369 <|> do{ escapeEmpty; return Nothing }
423 ; return (Left n) 370 <|> do{ esc <- escapeCode; return (Just esc) }
424 } 371 }
425 <|> decimalFloat 372
426 <|> fractFloat 0 373 escapeEmpty = char '&'
427 <|> return (Left 0) 374 escapeGap = do{ many1 space
428 375 ; char '\\' <?> "end of string gap"
429decimalFloat = do{ n <- decimal 376 }
430 ; option (Left n) 377
431 (fractFloat n) 378
432 } 379
433 380 -- escape codes
434fractFloat n = do{ f <- fractExponent n 381 escapeCode = charEsc <|> charNum <|> charAscii <|> charControl
435 ; return (Right f) 382 <?> "escape code"
436 } 383
437 384 charControl = do{ char '^'
438fractExponent n = do{ fract <- fraction 385 ; code <- upper
439 ; expo <- option 1.0 exponent' 386 ; return (toEnum (fromEnum code - fromEnum 'A'))
440 ; return ((fromInteger n + fract)*expo) 387 }
441 } 388
442 <|> 389 charNum = do{ code <- decimal
443 do{ expo <- exponent' 390 <|> do{ char 'o'; number 8 octDigit }
444 ; return ((fromInteger n)*expo) 391 <|> do{ char 'x'; number 16 hexDigit }
445 } 392 ; return (toEnum (fromInteger code))
446 393 }
447fraction = do{ char '.' 394
448 ; digits <- many1 digit <?> "fraction" 395 charEsc = choice (map parseEsc escMap)
449 ; return (foldr op 0.0 digits) 396 where
450 } 397 parseEsc (c,code) = do{ char c; return code }
451 <?> "fraction" 398
452 where 399 charAscii = choice (map parseAscii asciiMap)
453 op d f = (f + fromIntegral (digitToInt d))/10.0 400 where
454 401 parseAscii (asc,code) = try (do{ string asc; return code })
455exponent' = do{ oneOf "eE" 402
456 ; f <- sign 403
457 ; e <- decimal <?> "exponent" 404 -- escape code tables
458 ; return (power (f e)) 405 escMap = zip ("abfnrtv\\\"\'") ("\a\b\f\n\r\t\v\\\"\'")
459 } 406 asciiMap = zip (ascii3codes ++ ascii2codes) (ascii3 ++ ascii2)
460 <?> "exponent" 407
461 where 408 ascii2codes = ["BS","HT","LF","VT","FF","CR","SO","SI","EM",
462 power e | e < 0 = 1.0/power(-e) 409 "FS","GS","RS","US","SP"]
463 | otherwise = fromInteger (10^e) 410 ascii3codes = ["NUL","SOH","STX","ETX","EOT","ENQ","ACK","BEL",
464 411 "DLE","DC1","DC2","DC3","DC4","NAK","SYN","ETB",
465 412 "CAN","SUB","ESC","DEL"]
466-- integers and naturals 413
467int = do{ f <- lexeme sign 414 ascii2 = ['\BS','\HT','\LF','\VT','\FF','\CR','\SO','\SI',
468 ; n <- nat 415 '\EM','\FS','\GS','\RS','\US','\SP']
469 ; return (f n) 416 ascii3 = ['\NUL','\SOH','\STX','\ETX','\EOT','\ENQ','\ACK',
470 } 417 '\BEL','\DLE','\DC1','\DC2','\DC3','\DC4','\NAK',
471 418 '\SYN','\ETB','\CAN','\SUB','\ESC','\DEL']
472sign = (char '-' >> return negate) 419
473 <|> (char '+' >> return id) 420
474 <|> return id 421 -----------------------------------------------------------
475 422 -- Numbers
476nat = zeroNumber <|> decimal 423 -----------------------------------------------------------
477 424
478zeroNumber = do{ char '0' 425 -- floats
479 ; hexadecimal <|> octal <|> decimal <|> return 0 426 natFloat = do{ char '0'
480 } 427 ; zeroNumFloat
481 <?> "" 428 }
482 429 <|> decimalFloat
483decimal = number 10 digit 430
484hexadecimal = do{ oneOf "xX"; number 16 hexDigit } 431 zeroNumFloat = do{ n <- hexadecimal <|> octal
485octal = do{ oneOf "oO"; number 8 octDigit } 432 ; return (LInt n)
486 433 }
487number base baseDigit 434 <|> decimalFloat
488 = do{ digits <- many1 baseDigit 435 <|> fractFloat 0
489 ; let n = foldl' (\x d -> base*x + toInteger (digitToInt d)) 0 digits 436 <|> return (LInt 0)
490 ; seq n (return n) 437
491 } 438 decimalFloat = do{ n <- decimal
439 ; option (LInt n)
440 (fractFloat n)
441 }
442
443 fractFloat n = do{ f <- fractExponent n
444 ; return (LFloat f)
445 }
446
447 fractExponent n = do{ fract <- fraction
448 ; expo <- option 1.0 exponent'
449 ; return ((fromInteger n + fract)*expo)
450 }
451 <|>
452 do{ expo <- exponent'
453 ; return ((fromInteger n)*expo)
454 }
455
456 fraction = do{ char '.'
457 ; digits <- many1 digit <?> "fraction"
458 ; return (foldr op 0.0 digits)
459 }
460 <?> "fraction"
461 where
462 op d f = (f + fromIntegral (digitToInt d))/10.0
463
464 exponent' = do{ oneOf "eE"
465 ; f <- sign
466 ; e <- decimal <?> "exponent"
467 ; return (power (f e))
468 }
469 <?> "exponent"
470 where
471 power e | e < 0 = 1.0/power(-e)
472 | otherwise = fromInteger (10^e)
473
474
475 -- integers and naturals
476 sign = (char '-' >> return negate)
477 <|> (char '+' >> return id)
478 <|> return id
479
480 decimal = number 10 digit
481 hexadecimal = do{ oneOf "xX"; number 16 hexDigit }
482 octal = do{ oneOf "oO"; number 8 octDigit }
483
484 number base baseDigit
485 = do{ digits <- many1 baseDigit
486 ; let n = foldl' (\x d -> base*x + toInteger (digitToInt d)) 0 digits
487 ; seq n (return n)
488 }
492 489
493----------------------------------------------------------- 490-----------------------------------------------------------
494-- Operators & reserved ops 491-- Operators & reserved ops
diff --git a/src/LambdaCube/Compiler/Parser.hs b/src/LambdaCube/Compiler/Parser.hs
index 9ed694d9..bcaa4538 100644
--- a/src/LambdaCube/Compiler/Parser.hs
+++ b/src/LambdaCube/Compiler/Parser.hs
@@ -73,22 +73,6 @@ debug = False--True--tr
73 73
74try = try_ 74try = try_
75 75
76-------------------------------------------------------------------------------- literals
77
78data Lit
79 = LInt !Int
80 | LChar Char
81 | LFloat Double
82 | LString String
83 deriving (Eq)
84
85instance Show Lit where
86 show = \case
87 LFloat x -> show x
88 LString x -> show x
89 LInt x -> show x
90 LChar x -> show x
91
92-------------------------------------------------------------------------------- builtin precedences 76-------------------------------------------------------------------------------- builtin precedences
93 77
94data Prec 78data Prec
@@ -382,11 +366,7 @@ parseTerm prec = withRange setSI $ case prec of
382 PrecSwiz -> level PrecProj $ \t -> try "swizzling" $ mkSwizzling t <$> lexeme (char '%' *> manyNM 1 4 (satisfy (`elem` ("xyzwrgba" :: String)))) 366 PrecSwiz -> level PrecProj $ \t -> try "swizzling" $ mkSwizzling t <$> lexeme (char '%' *> manyNM 1 4 (satisfy (`elem` ("xyzwrgba" :: String))))
383 PrecProj -> level PrecAtom $ \t -> try "projection" $ mkProjection t <$ char '.' <*> sepBy1 (sLit . LString <$> lowerCase) (char '.') 367 PrecProj -> level PrecAtom $ \t -> try "projection" $ mkProjection t <$ char '.' <*> sepBy1 (sLit . LString <$> lowerCase) (char '.')
384 PrecAtom -> 368 PrecAtom ->
385 sLit . LChar <$> try "char literal" charLiteral 369 mkLit <$> namespace <*> try "literal" parseLit
386 <|> sLit . LString <$> stringLiteral
387 <|> sLit . LFloat <$> try "float literal" float
388 <|> sLit . LInt . fromIntegral <$ char '#' <*> natural -- todo: remove
389 <|> mkNat <$> namespace <*> natural
390 <|> Wildcard (Wildcard SType) <$ reserved "_" 370 <|> Wildcard (Wildcard SType) <$ reserved "_"
391 <|> char '\'' *> switchNS (parseTerm PrecAtom) 371 <|> char '\'' *> switchNS (parseTerm PrecAtom)
392 <|> sVar (try "identifier" upperLower) 372 <|> sVar (try "identifier" upperLower)
@@ -449,8 +429,9 @@ parseTerm prec = withRange setSI $ case prec of
449 mkList (Namespace (Just ExpLevel) _) xs = foldr (\x l -> SBuiltin "Cons" `SAppV` x `SAppV` l) (SBuiltin "Nil") xs 429 mkList (Namespace (Just ExpLevel) _) xs = foldr (\x l -> SBuiltin "Cons" `SAppV` x `SAppV` l) (SBuiltin "Nil") xs
450 mkList _ xs = error "mkList" 430 mkList _ xs = error "mkList"
451 431
452 mkNat (Namespace (Just ExpLevel) _) n = SBuiltin "fromInt" `SAppV` sLit (LInt $ fromIntegral n) 432 mkLit (Namespace (Just ExpLevel) _) n@LInt{} = SBuiltin "fromInt" `SAppV` sLit n
453 mkNat _ n = toNat n 433 mkLit _ (LInt n) = toNat n
434 mkLit _ l = sLit l
454 435
455 toNat 0 = SBuiltin "Zero" 436 toNat 0 = SBuiltin "Zero"
456 toNat n | n > 0 = SAppV (SBuiltin "Succ") $ toNat (n-1) 437 toNat n | n > 0 = SAppV (SBuiltin "Succ") $ toNat (n-1)
@@ -463,7 +444,7 @@ parseTerm prec = withRange setSI $ case prec of
463 calculatePrecs ns dcls = either fail return . f where 444 calculatePrecs ns dcls = either fail return . f where
464 f [] = error "impossible" 445 f [] = error "impossible"
465 f (Right t: xs) = either (\(op, xs) -> RightSection (calcPrec' t xs) op) (calcPrec' t) <$> cont xs 446 f (Right t: xs) = either (\(op, xs) -> RightSection (calcPrec' t xs) op) (calcPrec' t) <$> cont xs
466 f xs@(Left op@(_, "-"): _) = f $ Right (mkNat ns 0): xs 447 f xs@(Left op@(_, "-"): _) = f $ Right (mkLit ns $ LInt 0): xs
467 f (Left op: xs) = g op xs >>= either (const $ Left "TODO: better error message @476") 448 f (Left op: xs) = g op xs >>= either (const $ Left "TODO: better error message @476")
468 (\((op, e): oe) -> return $ LeftSection op $ calcPrec' e oe) 449 (\((op, e): oe) -> return $ LeftSection op $ calcPrec' e oe)
469 g op (Right t: xs) = (second ((op, t):) +++ ((op, t):)) <$> cont xs 450 g op (Right t: xs) = (second ((op, t):) +++ ((op, t):)) <$> cont xs
@@ -582,10 +563,7 @@ parsePat = \case
582 PCon <$> parseSIName upperCase <*> many (ParPat . pure <$> parsePat PrecAtom) 563 PCon <$> parseSIName upperCase <*> many (ParPat . pure <$> parsePat PrecAtom)
583 <|> parsePat PrecAtom 564 <|> parsePat PrecAtom
584 PrecAtom -> 565 PrecAtom ->
585 litP "primCompareFloat" . LFloat <$> try "float literal" float 566 mkLit <$> namespace <*> try "literal" parseLit
586 <|> litP "primCompareString" . LString <$> stringLiteral
587 <|> litP "primCompareChar" . LChar <$> try "char literal" charLiteral
588 <|> appRange (mkNatPat <$> namespace <*> natural)
589 <|> flip PCon [] <$> parseSIName upperCase 567 <|> flip PCon [] <$> parseSIName upperCase
590 <|> char '\'' *> switchNS (parsePat PrecAtom) 568 <|> char '\'' *> switchNS (parsePat PrecAtom)
591 <|> PVar <$> parseSIName patVar 569 <|> PVar <$> parseSIName patVar
@@ -593,8 +571,14 @@ parsePat = \case
593 <|> (\ns -> pConSI . mkTupPat ns) <$> namespace <*> parens patlist 571 <|> (\ns -> pConSI . mkTupPat ns) <$> namespace <*> parens patlist
594 where 572 where
595 litP s = flip ViewPat (ParPat [PCon (mempty, "EQ") []]) . SAppV (SBuiltin s) . sLit 573 litP s = flip ViewPat (ParPat [PCon (mempty, "EQ") []]) . SAppV (SBuiltin s) . sLit
596 mkNatPat (Namespace (Just ExpLevel) _) n si = litP "primCompareInt" . LInt $ fromIntegral n 574
597 mkNatPat _ n si = toNatP si n 575 mkLit (Namespace (Just ExpLevel) _) n@LInt{} = litP "primCompareInt" n
576 mkLit _ (LInt n) = toNatP n
577 mkLit _ n = litP (f n) n where
578 f LFloat{} = "primCompareFloat"
579 f LString{} = "primCompareString"
580 f LChar{} = "primCompareChar"
581
598 pConSI (PCon (_, n) ps) = PCon (sourceInfo ps, n) ps 582 pConSI (PCon (_, n) ps) = PCon (sourceInfo ps, n) ps
599 pConSI p = p 583 pConSI p = p
600 584
@@ -613,9 +597,9 @@ parsePat = \case
613 597
614 calculatePatPrecs dcls (e, xs) = calcPrec (\op x y -> PCon op $ ParPat . (:[]) <$> [x, y]) (getFixity dcls . snd) e xs 598 calculatePatPrecs dcls (e, xs) = calcPrec (\op x y -> PCon op $ ParPat . (:[]) <$> [x, y]) (getFixity dcls . snd) e xs
615 599
616 toNatP si = run where 600 toNatP = run where
617 run 0 = PCon (si, "Zero") [] 601 run 0 = PCon (mempty, "Zero") []
618 run n | n > 0 = PCon (si, "Succ") [ParPat [run $ n-1]] 602 run n | n > 0 = PCon (mempty, "Succ") [ParPat [run $ n-1]]
619 603
620 604
621longPattern = parsePat PrecAnn <&> (getPVars &&& id) 605longPattern = parsePat PrecAnn <&> (getPVars &&& id)
diff --git a/testdata/Builtins.out b/testdata/Builtins.out
index 6f407c39..7e947fa9 100644
--- a/testdata/Builtins.out
+++ b/testdata/Builtins.out
@@ -73,10 +73,8 @@ testdata/Builtins.lc 31:52-31:53 Type
73testdata/Builtins.lc 31:54-31:55 Nat 73testdata/Builtins.lc 31:54-31:55 Nat
74testdata/Builtins.lc 33:29-33:32 Type 74testdata/Builtins.lc 33:29-33:32 Type
75testdata/Builtins.lc 34:5-34:14 Nat -> Type->Type 75testdata/Builtins.lc 34:5-34:14 Nat -> Type->Type
76testdata/Builtins.lc 34:15-34:16 Nat
77testdata/Builtins.lc 34:15-35:60 Nat -> Type->Type | Type | Type->Type
78testdata/Builtins.lc 34:21-34:22 Type 76testdata/Builtins.lc 34:21-34:22 Type
79testdata/Builtins.lc 34:21-35:60 Nat->Type 77testdata/Builtins.lc 34:21-35:60 Nat -> Type->Type | Nat->Type | Type->Type
80testdata/Builtins.lc 35:37-35:40 Nat -> Type->Type 78testdata/Builtins.lc 35:37-35:40 Nat -> Type->Type
81testdata/Builtins.lc 35:37-35:58 Type->Type 79testdata/Builtins.lc 35:37-35:58 Type->Type
82testdata/Builtins.lc 35:37-35:60 Nat->Type | Type 80testdata/Builtins.lc 35:37-35:60 Nat->Type | Type
@@ -589,7 +587,7 @@ testdata/Builtins.lc 110:20-112:12 ({a : Component V0} -> V1 -> V2 -> V3 -> Vec
589testdata/Builtins.lc 110:20-113:12 ({a : Component V0} -> V1 -> V2 -> V3 -> V4 -> VecS V5 4) -> {g : Component V1} -> V2 -> V3 -> V4 -> V5 -> VecS V6 4 587testdata/Builtins.lc 110:20-113:12 ({a : Component V0} -> V1 -> V2 -> V3 -> V4 -> VecS V5 4) -> {g : Component V1} -> V2 -> V3 -> V4 -> V5 -> VecS V6 4
590testdata/Builtins.lc 110:20-114:19 {a : Component V0}->V1 -> {c : Component V1}->V2 588testdata/Builtins.lc 110:20-114:19 {a : Component V0}->V1 -> {c : Component V1}->V2
591testdata/Builtins.lc 110:20-115:17 {a : Component V0}->V1 -> {c : Component V1}->V2 589testdata/Builtins.lc 110:20-115:17 {a : Component V0}->V1 -> {c : Component V1}->V2
592testdata/Builtins.lc 110:20-136:33 Type | Type->Type 590testdata/Builtins.lc 110:20-136:31 Type | Type->Type
593testdata/Builtins.lc 110:20-157:12 {a : Component V0} -> V1 -> V2 -> VecS V3 2 | {a} -> {b : Component a} -> a -> a -> VecS a 2 591testdata/Builtins.lc 110:20-157:12 {a : Component V0} -> V1 -> V2 -> VecS V3 2 | {a} -> {b : Component a} -> a -> a -> VecS a 2
594testdata/Builtins.lc 110:20-158:12 {a : Component V0} -> V1 -> V2 -> V3 -> VecS V4 3 | {a} -> {b : Component a} -> a -> a -> a -> VecS a 3 592testdata/Builtins.lc 110:20-158:12 {a : Component V0} -> V1 -> V2 -> V3 -> VecS V4 3 | {a} -> {b : Component a} -> a -> a -> a -> VecS a 3
595testdata/Builtins.lc 110:20-159:12 {a : Component V0} -> V1 -> V2 -> V3 -> V4 -> VecS V5 4 | {a} -> {b : Component a} -> a -> a -> a -> a -> VecS a 4 593testdata/Builtins.lc 110:20-159:12 {a : Component V0} -> V1 -> V2 -> V3 -> V4 -> VecS V5 4 | {a} -> {b : Component a} -> a -> a -> a -> a -> VecS a 4
@@ -606,7 +604,7 @@ testdata/Builtins.lc 116:20-118:12 ({a : Component V0} -> V1 -> V2 -> V3 -> Vec
606testdata/Builtins.lc 116:20-119:12 ({a : Component V0} -> V1 -> V2 -> V3 -> V4 -> VecS V5 4) -> {g : Component V1} -> V2 -> V3 -> V4 -> V5 -> VecS V6 4 604testdata/Builtins.lc 116:20-119:12 ({a : Component V0} -> V1 -> V2 -> V3 -> V4 -> VecS V5 4) -> {g : Component V1} -> V2 -> V3 -> V4 -> V5 -> VecS V6 4
607testdata/Builtins.lc 116:20-120:22 {a : Component V0}->V1 -> {c : Component V1}->V2 605testdata/Builtins.lc 116:20-120:22 {a : Component V0}->V1 -> {c : Component V1}->V2
608testdata/Builtins.lc 116:20-121:21 {a : Component V0}->V1 -> {c : Component V1}->V2 606testdata/Builtins.lc 116:20-121:21 {a : Component V0}->V1 -> {c : Component V1}->V2
609testdata/Builtins.lc 116:20-136:33 Type 607testdata/Builtins.lc 116:20-136:31 Type
610testdata/Builtins.lc 116:20-157:12 {a : Component V0} -> V1 -> V2 -> VecS V3 2 608testdata/Builtins.lc 116:20-157:12 {a : Component V0} -> V1 -> V2 -> VecS V3 2
611testdata/Builtins.lc 116:20-158:12 {a : Component V0} -> V1 -> V2 -> V3 -> VecS V4 3 609testdata/Builtins.lc 116:20-158:12 {a : Component V0} -> V1 -> V2 -> V3 -> VecS V4 3
612testdata/Builtins.lc 116:20-159:12 {a : Component V0} -> V1 -> V2 -> V3 -> V4 -> VecS V5 4 610testdata/Builtins.lc 116:20-159:12 {a : Component V0} -> V1 -> V2 -> V3 -> V4 -> VecS V5 4
@@ -627,7 +625,7 @@ testdata/Builtins.lc 123:20-125:12 ({a : Component V0} -> V1 -> V2 -> V3 -> Vec
627testdata/Builtins.lc 123:20-126:12 ({a : Component V0} -> V1 -> V2 -> V3 -> V4 -> VecS V5 4) -> {g : Component V1} -> V2 -> V3 -> V4 -> V5 -> VecS V6 4 625testdata/Builtins.lc 123:20-126:12 ({a : Component V0} -> V1 -> V2 -> V3 -> V4 -> VecS V5 4) -> {g : Component V1} -> V2 -> V3 -> V4 -> V5 -> VecS V6 4
628testdata/Builtins.lc 123:20-127:23 {a : Component V0}->V1 -> {c : Component V1}->V2 626testdata/Builtins.lc 123:20-127:23 {a : Component V0}->V1 -> {c : Component V1}->V2
629testdata/Builtins.lc 123:20-128:22 {a : Component V0}->V1 -> {c : Component V1}->V2 627testdata/Builtins.lc 123:20-128:22 {a : Component V0}->V1 -> {c : Component V1}->V2
630testdata/Builtins.lc 123:20-136:33 Type 628testdata/Builtins.lc 123:20-136:31 Type
631testdata/Builtins.lc 123:20-157:12 {a : Component V0} -> V1 -> V2 -> VecS V3 2 629testdata/Builtins.lc 123:20-157:12 {a : Component V0} -> V1 -> V2 -> VecS V3 2
632testdata/Builtins.lc 123:20-158:12 {a : Component V0} -> V1 -> V2 -> V3 -> VecS V4 3 630testdata/Builtins.lc 123:20-158:12 {a : Component V0} -> V1 -> V2 -> V3 -> VecS V4 3
633testdata/Builtins.lc 123:20-159:12 {a : Component V0} -> V1 -> V2 -> V3 -> V4 -> VecS V5 4 631testdata/Builtins.lc 123:20-159:12 {a : Component V0} -> V1 -> V2 -> V3 -> V4 -> VecS V5 4
@@ -648,7 +646,7 @@ testdata/Builtins.lc 130:20-132:12 ({a : Component V0} -> V1 -> V2 -> V3 -> Vec
648testdata/Builtins.lc 130:20-133:12 ({a : Component V0} -> V1 -> V2 -> V3 -> V4 -> VecS V5 4) -> {g : Component V1} -> V2 -> V3 -> V4 -> V5 -> VecS V6 4 646testdata/Builtins.lc 130:20-133:12 ({a : Component V0} -> V1 -> V2 -> V3 -> V4 -> VecS V5 4) -> {g : Component V1} -> V2 -> V3 -> V4 -> V5 -> VecS V6 4
649testdata/Builtins.lc 130:20-134:17 {a : Component V0}->V1 -> {c : Component V1}->V2 647testdata/Builtins.lc 130:20-134:17 {a : Component V0}->V1 -> {c : Component V1}->V2
650testdata/Builtins.lc 130:20-135:16 {a : Component V0}->V1 -> {c : Component V1}->V2 648testdata/Builtins.lc 130:20-135:16 {a : Component V0}->V1 -> {c : Component V1}->V2
651testdata/Builtins.lc 130:20-136:33 Type 649testdata/Builtins.lc 130:20-136:31 Type
652testdata/Builtins.lc 130:20-157:12 {a : Component V0} -> V1 -> V2 -> VecS V3 2 650testdata/Builtins.lc 130:20-157:12 {a : Component V0} -> V1 -> V2 -> VecS V3 2
653testdata/Builtins.lc 130:20-158:12 {a : Component V0} -> V1 -> V2 -> V3 -> VecS V4 3 651testdata/Builtins.lc 130:20-158:12 {a : Component V0} -> V1 -> V2 -> V3 -> VecS V4 3
654testdata/Builtins.lc 130:20-159:12 {a : Component V0} -> V1 -> V2 -> V3 -> V4 -> VecS V5 4 652testdata/Builtins.lc 130:20-159:12 {a : Component V0} -> V1 -> V2 -> V3 -> V4 -> VecS V5 4
@@ -659,7 +657,7 @@ testdata/Builtins.lc 132:10-132:12 {a} -> a -> a -> a -> VecS a 3
659testdata/Builtins.lc 133:10-133:12 {a} -> a -> a -> a -> a -> VecS a 4 657testdata/Builtins.lc 133:10-133:12 {a} -> a -> a -> a -> a -> VecS a 4
660testdata/Builtins.lc 134:14-134:17 Float 658testdata/Builtins.lc 134:14-134:17 Float
661testdata/Builtins.lc 135:13-135:16 Float 659testdata/Builtins.lc 135:13-135:16 Float
662testdata/Builtins.lc 136:26-136:33 Type 660testdata/Builtins.lc 136:26-136:31 Type
663testdata/Builtins.lc 136:26-157:12 ({a : Component V0} -> V1 -> V2 -> VecS V3 2) -> {e : Component V1} -> V2 -> V3 -> VecS V4 2 661testdata/Builtins.lc 136:26-157:12 ({a : Component V0} -> V1 -> V2 -> VecS V3 2) -> {e : Component V1} -> V2 -> V3 -> VecS V4 2
664testdata/Builtins.lc 136:26-158:12 ({a : Component V0} -> V1 -> V2 -> V3 -> VecS V4 3) -> {f : Component V1} -> V2 -> V3 -> V4 -> VecS V5 3 662testdata/Builtins.lc 136:26-158:12 ({a : Component V0} -> V1 -> V2 -> V3 -> VecS V4 3) -> {f : Component V1} -> V2 -> V3 -> V4 -> VecS V5 3
665testdata/Builtins.lc 136:26-159:12 ({a : Component V0} -> V1 -> V2 -> V3 -> V4 -> VecS V5 4) -> {g : Component V1} -> V2 -> V3 -> V4 -> V5 -> VecS V6 4 663testdata/Builtins.lc 136:26-159:12 ({a : Component V0} -> V1 -> V2 -> V3 -> V4 -> VecS V5 4) -> {g : Component V1} -> V2 -> V3 -> V4 -> V5 -> VecS V6 4
@@ -759,9 +757,9 @@ testdata/Builtins.lc 166:25-166:29 Type
759testdata/Builtins.lc 168:7-168:15 Type->Type 757testdata/Builtins.lc 168:7-168:15 Type->Type
760testdata/Builtins.lc 170:25-170:30 Type 758testdata/Builtins.lc 170:25-170:30 Type
761testdata/Builtins.lc 170:25-174:39 Type | Type->Type 759testdata/Builtins.lc 170:25-174:39 Type | Type->Type
762testdata/Builtins.lc 171:31-171:38 Type 760testdata/Builtins.lc 171:31-171:36 Type
763testdata/Builtins.lc 171:31-174:39 Type 761testdata/Builtins.lc 171:31-174:39 Type
764testdata/Builtins.lc 174:30-174:39 Type 762testdata/Builtins.lc 174:34-174:39 Type
765testdata/Builtins.lc 184:6-184:20 Type 763testdata/Builtins.lc 184:6-184:20 Type
766testdata/Builtins.lc 184:6-199:23 Type 764testdata/Builtins.lc 184:6-199:23 Type
767testdata/Builtins.lc 185:7-185:12 BlendingFactor 765testdata/Builtins.lc 185:7-185:12 BlendingFactor
@@ -1593,7 +1591,7 @@ testdata/Builtins.lc 427:29-427:42 {a} -> {b} -> {c : DefaultFragOp b} -> Fragm
1593testdata/Builtins.lc 427:46-427:63 Type->Type 1591testdata/Builtins.lc 427:46-427:63 Type->Type
1594testdata/Builtins.lc 427:46-427:65 Type 1592testdata/Builtins.lc 427:46-427:65 Type
1595testdata/Builtins.lc 427:64-427:65 Type 1593testdata/Builtins.lc 427:64-427:65 Type
1596testdata/Builtins.lc 428:37-428:44 Type 1594testdata/Builtins.lc 428:37-428:42 Type
1597testdata/Builtins.lc 428:37-428:112 ({a : DefaultFragOp V1} -> FragmentOperation V2) -> {c : DefaultFragOp V2} -> FragmentOperation V3 1595testdata/Builtins.lc 428:37-428:112 ({a : DefaultFragOp V1} -> FragmentOperation V2) -> {c : DefaultFragOp V2} -> FragmentOperation V3
1598testdata/Builtins.lc 428:37-429:36 Type | Type->Type 1596testdata/Builtins.lc 428:37-429:36 Type | Type->Type
1599testdata/Builtins.lc 428:37-429:77 {a : DefaultFragOp V1} -> FragmentOperation V2 | {a} -> {b : DefaultFragOp a} -> FragmentOperation a 1597testdata/Builtins.lc 428:37-429:77 {a : DefaultFragOp V1} -> FragmentOperation V2 | {a} -> {b : DefaultFragOp a} -> FragmentOperation a
diff --git a/testdata/language-features/basic-values/def05.reject.out b/testdata/language-features/basic-values/def05.reject.out
index 616c6884..59c1b1c2 100644
--- a/testdata/language-features/basic-values/def05.reject.out
+++ b/testdata/language-features/basic-values/def05.reject.out
@@ -1,4 +1,4 @@
1"testdata/language-features/basic-values/def05.reject.lc" (line 4, column 1): 1"testdata/language-features/basic-values/def05.reject.lc" (line 4, column 1):
2unexpected end of input 2unexpected end of input
3expecting projection, swizzling, "@", char literal, literal string, float literal, "#", natural, "_", "'", identifier, "[", "(", "{", "let", symbols, backquoted ident, "~", expression, lambda, "::", "->", "=>", "where", "data", "class", "instance", type family, type instance, "type", typed ident, "infix", "infixl", "infixr", operator definition, lhs or pattern 3expecting projection, swizzling, "@", literal, "_", "'", identifier, "[", "(", "{", "let", symbols, backquoted ident, "~", expression, lambda, "::", "->", "=>", "where", "data", "class", "instance", type family, type instance, "type", typed ident, "infix", "infixl", "infixr", operator definition, lhs or pattern
4different number of arguments of fun at testdata/language-features/basic-values/def05.reject.lc 1:1-1:4 \ No newline at end of file 4different number of arguments of fun at testdata/language-features/basic-values/def05.reject.lc 1:1-1:4 \ No newline at end of file
diff --git a/testdata/language-features/basic-values/def06.reject.out b/testdata/language-features/basic-values/def06.reject.out
index 79952277..852fa677 100644
--- a/testdata/language-features/basic-values/def06.reject.out
+++ b/testdata/language-features/basic-values/def06.reject.out
@@ -1,4 +1,4 @@
1"testdata/language-features/basic-values/def06.reject.lc" (line 5, column 1): 1"testdata/language-features/basic-values/def06.reject.lc" (line 5, column 1):
2unexpected end of input 2unexpected end of input
3expecting projection, swizzling, "@", char literal, literal string, float literal, "#", natural, "_", "'", identifier, "[", "(", "{", "let", symbols, backquoted ident, "~", expression, lambda, "::", "->", "=>", "where", "data", "class", "instance", type family, type instance, "type", typed ident, "infix", "infixl", "infixr", operator definition, lhs or pattern 3expecting projection, swizzling, "@", literal, "_", "'", identifier, "[", "(", "{", "let", symbols, backquoted ident, "~", expression, lambda, "::", "->", "=>", "where", "data", "class", "instance", type family, type instance, "type", typed ident, "infix", "infixl", "infixr", operator definition, lhs or pattern
4different number of arguments of fun2 at testdata/language-features/basic-values/def06.reject.lc 1:1-1:5 \ No newline at end of file 4different number of arguments of fun2 at testdata/language-features/basic-values/def06.reject.lc 1:1-1:5 \ No newline at end of file
diff --git a/testdata/language-features/basic-values/redefine03.reject.out b/testdata/language-features/basic-values/redefine03.reject.out
index e0050e16..95b587a1 100644
--- a/testdata/language-features/basic-values/redefine03.reject.out
+++ b/testdata/language-features/basic-values/redefine03.reject.out
@@ -1,4 +1,4 @@
1"testdata/language-features/basic-values/redefine03.reject.lc" (line 4, column 1): 1"testdata/language-features/basic-values/redefine03.reject.lc" (line 4, column 1):
2unexpected end of input 2unexpected end of input
3expecting projection, swizzling, "@", char literal, literal string, float literal, "#", natural, "_", "'", identifier, "[", "(", "{", "let", symbols, backquoted ident, "~", expression, lambda, "::", "->", "=>", "where", "data", "class", "instance", type family, type instance, "type", typed ident, "infix", "infixl", "infixr", operator definition, lhs or pattern 3expecting projection, swizzling, "@", literal, "_", "'", identifier, "[", "(", "{", "let", symbols, backquoted ident, "~", expression, lambda, "::", "->", "=>", "where", "data", "class", "instance", type family, type instance, "type", typed ident, "infix", "infixl", "infixr", operator definition, lhs or pattern
4redefined x at testdata/language-features/basic-values/redefine03.reject.lc 2:9-2:10 \ No newline at end of file 4redefined x at testdata/language-features/basic-values/redefine03.reject.lc 2:9-2:10 \ No newline at end of file
diff --git a/testdata/language-features/guard/guard10.reject.out b/testdata/language-features/guard/guard10.reject.out
index 5b95a423..be68325a 100644
--- a/testdata/language-features/guard/guard10.reject.out
+++ b/testdata/language-features/guard/guard10.reject.out
@@ -1,3 +1,3 @@
1"testdata/language-features/guard/guard10.reject.lc" (line 2, column 1): 1"testdata/language-features/guard/guard10.reject.lc" (line 2, column 1):
2unexpected '|' 2unexpected '|'
3expecting projection, swizzling, "@", char literal, literal string, float literal, "#", natural, "_", "'", identifier, "[", "(", "{", "let", symbols, backquoted ident, "~", expression, lambda, "::", "->", "=>", "|", "data", "class", "instance", type family, type instance, "type", typed ident, "infix", "infixl", "infixr", operator definition, lhs, pattern or end of input \ No newline at end of file 3expecting projection, swizzling, "@", literal, "_", "'", identifier, "[", "(", "{", "let", symbols, backquoted ident, "~", expression, lambda, "::", "->", "=>", "|", "data", "class", "instance", type family, type instance, "type", typed ident, "infix", "infixl", "infixr", operator definition, lhs, pattern or end of input \ No newline at end of file
diff --git a/testdata/listcompr01.reject.out b/testdata/listcompr01.reject.out
index 94560015..81949c98 100644
--- a/testdata/listcompr01.reject.out
+++ b/testdata/listcompr01.reject.out
@@ -1,3 +1,3 @@
1"testdata/listcompr01.reject.lc" (line 6, column 42): 1"testdata/listcompr01.reject.lc" (line 6, column 42):
2unexpected ',' 2unexpected ','
3expecting projection, swizzling, "@", char literal, literal string, float literal, "#", natural, "_", "'", identifier, "[", "(", "{", "let", symbols, backquoted ident, "~", expression, lambda, "::", "->", "=>", "where", "data", "class", "instance", type family, type instance, "type", typed ident, "infix", "infixl", "infixr", operator definition, lhs, pattern or end of input \ No newline at end of file 3expecting projection, swizzling, "@", literal, "_", "'", identifier, "[", "(", "{", "let", symbols, backquoted ident, "~", expression, lambda, "::", "->", "=>", "where", "data", "class", "instance", type family, type instance, "type", typed ident, "infix", "infixl", "infixr", operator definition, lhs, pattern or end of input \ No newline at end of file