Skip to content
Snippets Groups Projects
Commit f3262fe8 authored by Gergő Érdi's avatar Gergő Érdi
Browse files

Add test cases for explicitly-bidirectional pattern synonym

parent 32bf8a5f
No related merge requests found
......@@ -1068,6 +1068,8 @@ mk/ghcconfig_*_inplace_bin_ghc-stage2.exe.mk
/tests/parser/unicode/1744
/tests/parser/unicode/T1744
/tests/parser/unicode/utf8_024
/tests/patsyn/should_run/bidir-explicit
/tests/patsyn/should_run/bidir-explicit-scope
/tests/patsyn/should_run/eval
/tests/patsyn/should_run/ex-prov
/tests/patsyn/should_run/ex-prov-run
......
test('eval', normal, compile_and_run, [''])
test('match', normal, compile_and_run, [''])
test('ex-prov-run', normal, compile_and_run, [''])
test('bidir-explicit', normal, compile_and_run, [''])
test('bidir-explicit-scope', normal, compile_and_run, [''])
{-# LANGUAGE PatternSynonyms #-}
module Main where
pattern First x <- x:_ where
First x = foo [x, x, x]
foo :: [a] -> [a]
foo xs@(First x) = replicate (length xs + 1) x
main = mapM_ print $ First ()
()
()
()
()
{-# LANGUAGE PatternSynonyms #-}
module Main where
pattern First x <- x:_ where
First x = [x]
main = mapM_ print $ First ()
()
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment