[commit: haddock] master: Create hyperlinker test case with quantified type variables. (571944f)

git at git.haskell.org git at git.haskell.org
Wed Jul 8 08:42:14 UTC 2015


Repository : ssh://git@git.haskell.org/haddock

On branch  : master
Link       : http://git.haskell.org/haddock.git/commitdiff/571944f4a81feae7e04b05d1549a19e0b677f4eb

>---------------------------------------------------------------

commit 571944f4a81feae7e04b05d1549a19e0b677f4eb
Author: Łukasz Hanuszczak <lukasz.hanuszczak at gmail.com>
Date:   Wed Jul 1 19:28:32 2015 +0200

    Create hyperlinker test case with quantified type variables.


>---------------------------------------------------------------

571944f4a81feae7e04b05d1549a19e0b677f4eb
 hypsrc-test/src/Polymorphism.hs | 55 +++++++++++++++++++++++++++++++++++++++++
 1 file changed, 55 insertions(+)

diff --git a/hypsrc-test/src/Polymorphism.hs b/hypsrc-test/src/Polymorphism.hs
new file mode 100644
index 0000000..2e1a93b
--- /dev/null
+++ b/hypsrc-test/src/Polymorphism.hs
@@ -0,0 +1,55 @@
+{-# LANGUAGE RankNTypes #-}
+
+
+module Polymorphism where
+
+
+foo :: a -> a -> a
+foo = undefined
+
+foo' :: forall a. a -> a -> a
+foo' = undefined
+
+bar :: a -> b -> (a, b)
+bar = undefined
+
+bar' :: forall a b. a -> b -> (a, b)
+bar' = undefined
+
+baz :: a -> (a -> [a -> a] -> b) -> b
+baz = undefined
+
+baz' :: forall a b. a -> (a -> [a -> a] -> b) -> b
+baz' = undefined
+
+quux :: a -> (forall a. a -> a) -> a
+quux = undefined
+
+quux' :: forall a. a -> (forall a. a -> a) -> a
+quux' = undefined
+
+
+num :: Num a => a -> a -> a
+num = undefined
+
+num' :: forall a. Num a => a -> a -> a
+num' = undefined
+
+eq :: (Eq a, Eq b) => [a] -> [b] -> (a, b)
+eq = undefined
+
+eq' :: forall a b. (Eq a, Eq b) => [a] -> [b] -> (a, b)
+eq' = undefined
+
+mon :: Monad m => (a -> m a) -> m a
+mon = undefined
+
+mon' :: forall m a. Monad m => (a -> m a) -> m a
+mon' = undefined
+
+
+norf :: a -> (forall a. Ord a => a -> a) -> a
+norf = undefined
+
+norf' :: forall a. a -> (forall a. Ord a => a -> a) -> a
+norf' = undefined



More information about the ghc-commits mailing list