Skip to content
Snippets Groups Projects
Commit 9d91014f authored by sof's avatar sof
Browse files

[project @ 1998-04-30 20:36:09 by sof]

new local universal quant test
parent 17f2e4ce
No related merge requests found
ghc: module version changed to 1; reason: no old .hi file
_exports_
ShouldSucceed main x;
_declarations_
1 main _:_ PrelIOBase.IO PrelBase.() ;;
1 x _:_ PrelBase.Double ;;
--!!! Local universal quantification.
module ShouldSucceed where
import PrelGHC -- to get at All
data Monad2 m = MkMonad2 (All a => a -> m a)
((All a, All b) => m a -> (a -> m b) -> m b)
halfListMonad :: ((All a, All b) => [a] -> (a -> [b]) -> [b]) -> Monad2 []
halfListMonad b = MkMonad2 (\x -> [x]) b
ghc: module version changed to 1; reason: no old .hi file
_exports_
ShouldSucceed halfListMonad Monad2(MkMonad2);
_instances_
instance _forall_ [a :: (* -> *)] => {PrelBase.Eval (Monad2 a)} = $dEvalMonad20;
_declarations_
1 $dEvalMonad20 _:_ _forall_ [a :: (* -> *)] => {PrelBase.Eval (Monad2 a)} ;;
1 data Monad2 m :: (* -> *) = MkMonad2 (_forall_ [a] => a -> m a) (_forall_ [a b] => m a -> (a -> m b) -> m b) ;
1 halfListMonad _:_ (_forall_ [a b] => [a] -> (a -> [b]) -> [b]) -> Monad2 PrelBase.[] ;;
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