[commit: base] master: Catch an illegal pragma and fix a typo (100c051)

Gabor Greif ggreif at gmail.com
Thu Jun 27 01:09:16 CEST 2013


Repository : ssh://darcs.haskell.org//srv/darcs/packages/base

On branch  : master

https://github.com/ghc/packages-base/commit/100c0517b5dd36a58e399df2bc34d3db98957845

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

commit 100c0517b5dd36a58e399df2bc34d3db98957845
Author: Gabor Greif <ggreif at gmail.com>
Date:   Thu Jun 27 01:06:22 2013 +0200

    Catch an illegal pragma and fix a typo

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

 GHC/TypeLits.hs |    4 ++--
 1 files changed, 2 insertions(+), 2 deletions(-)

diff --git a/GHC/TypeLits.hs b/GHC/TypeLits.hs
index 68b0d79..c2e4906 100644
--- a/GHC/TypeLits.hs
+++ b/GHC/TypeLits.hs
@@ -158,7 +158,7 @@ instance (SingI a, SingE (KindOf a)) => SingRep (a :: k)
 
 -- The type of an unknown singletons of a given kind.
 -- Note that the "type" parameter on this type is really
--- a *kind* parameter (this is simillar to the trick used in `SingE`).
+-- a *kind* parameter (this is similar to the trick used in `SingE`).
 data SomeSing :: KindIs k -> * where
   SomeSing :: SingI (n::k) => proxy n -> SomeSing (kp :: KindIs k)
 
@@ -212,7 +212,7 @@ incoherentForgetSing x = withSingI x it LocalProxy
   it :: SingI n => LocalProxy n -> SomeSing kp
   it = SomeSing
 
-{-# LANGUAGE NOINLINE withSingI #-}
+{-# NOINLINE withSingI #-}
 withSingI :: Sing n -> (SingI n => a) -> a
 withSingI x = magicSingI x ((\f -> f) :: () -> ())
 





More information about the ghc-commits mailing list