Skip to content

Commit

Permalink
Update base for new Safe Haskell design
Browse files Browse the repository at this point in the history
  • Loading branch information
David Terei committed Oct 25, 2011
1 parent 914703a commit 447448a
Show file tree
Hide file tree
Showing 56 changed files with 67 additions and 8 deletions.
6 changes: 4 additions & 2 deletions Control/Monad/ST.hs
@@ -1,6 +1,8 @@
{-# LANGUAGE CPP, SafeImports #-}
{-# LANGUAGE CPP #-}
#if sh_SAFE_DEFAULT
{-# LANGUAGE Safe #-}
#else
{-# LANGUAGE Unsafe #-}
#endif

-----------------------------------------------------------------------------
Expand Down Expand Up @@ -29,7 +31,7 @@ module Control.Monad.ST (
#endif
) where

import safe Control.Monad.ST.Safe
import Control.Monad.ST.Safe

#if !sh_SAFE_DEFAULT
import qualified Control.Monad.ST.Unsafe as U
Expand Down
1 change: 1 addition & 0 deletions Control/Monad/ST/Imp.hs
@@ -1,3 +1,4 @@
{-# LANGUAGE Unsafe #-}
{-# LANGUAGE CPP #-}
{-# OPTIONS_HADDOCK hide #-}

Expand Down
6 changes: 4 additions & 2 deletions Control/Monad/ST/Lazy.hs
@@ -1,6 +1,8 @@
{-# LANGUAGE CPP, SafeImports #-}
{-# LANGUAGE CPP #-}
#if sh_SAFE_DEFAULT
{-# LANGUAGE Safe #-}
#else
{-# LANGUAGE Unsafe #-}
#endif

-----------------------------------------------------------------------------
Expand Down Expand Up @@ -28,7 +30,7 @@ module Control.Monad.ST.Lazy (
#endif
) where

import safe Control.Monad.ST.Lazy.Safe
import Control.Monad.ST.Lazy.Safe
#if !sh_SAFE_DEFAULT
import qualified Control.Monad.ST.Lazy.Unsafe as U

Expand Down
1 change: 1 addition & 0 deletions Control/Monad/ST/Lazy/Imp.hs
@@ -1,3 +1,4 @@
{-# LANGUAGE Unsafe #-}
{-# LANGUAGE CPP, MagicHash, UnboxedTuples, Rank2Types #-}
{-# OPTIONS_HADDOCK hide #-}

Expand Down
1 change: 1 addition & 0 deletions Control/Monad/ST/Lazy/Unsafe.hs
@@ -1,3 +1,4 @@
{-# LANGUAGE Unsafe #-}
-----------------------------------------------------------------------------
-- |
-- Module : Control.Monad.ST.Lazy.Unsafe
Expand Down
2 changes: 2 additions & 0 deletions Control/Monad/ST/Strict.hs
@@ -1,6 +1,8 @@
{-# LANGUAGE CPP #-}
#if sh_SAFE_DEFAULT
{-# LANGUAGE Safe #-}
#else
{-# LANGUAGE Unsafe #-}
#endif
-----------------------------------------------------------------------------
-- |
Expand Down
1 change: 1 addition & 0 deletions Control/Monad/ST/Unsafe.hs
@@ -1,3 +1,4 @@
{-# LANGUAGE Unsafe #-}
-----------------------------------------------------------------------------
-- |
-- Module : Control.Monad.ST.Unsafe
Expand Down
1 change: 1 addition & 0 deletions Data/Typeable.hs-boot
@@ -1,3 +1,4 @@
{-# LANGUAGE Trustworthy #-}
{-# LANGUAGE NoImplicitPrelude #-}

module Data.Typeable (Typeable, mkTyConApp, cast) where
Expand Down
1 change: 1 addition & 0 deletions Data/Typeable/Internal.hs
@@ -1,3 +1,4 @@
{-# LANGUAGE Unsafe #-}
-----------------------------------------------------------------------------
-- |
-- Module : Data.Typeable.Internal
Expand Down
1 change: 1 addition & 0 deletions Data/Typeable/Internal.hs-boot
@@ -1,3 +1,4 @@
{-# LANGUAGE Unsafe #-}
{-# LANGUAGE CPP, NoImplicitPrelude, MagicHash #-}
module Data.Typeable.Internal (
Typeable(typeOf),
Expand Down
1 change: 1 addition & 0 deletions Debug/Trace.hs
@@ -1,3 +1,4 @@
{-# LANGUAGE Unsafe #-}
{-# LANGUAGE CPP, ForeignFunctionInterface #-}

-----------------------------------------------------------------------------
Expand Down
2 changes: 2 additions & 0 deletions Foreign.hs
@@ -1,5 +1,7 @@
#if sh_SAFE_DEFAULT
{-# LANGUAGE Trustworthy #-}
#else
{-# LANGUAGE Unsafe #-}
#endif
{-# LANGUAGE NoImplicitPrelude #-}

Expand Down
6 changes: 4 additions & 2 deletions Foreign/ForeignPtr.hs
@@ -1,6 +1,8 @@
{-# LANGUAGE SafeImports, CPP, NoImplicitPrelude #-}
{-# LANGUAGE CPP, NoImplicitPrelude #-}
#if sh_SAFE_DEFAULT
{-# LANGUAGE Trustworthy #-}
#else
{-# LANGUAGE Unsafe #-}
#endif
{-# OPTIONS_HADDOCK hide #-}

Expand Down Expand Up @@ -28,7 +30,7 @@ module Foreign.ForeignPtr (
#endif
) where

import safe Foreign.ForeignPtr.Safe
import Foreign.ForeignPtr.Safe

#if !sh_SAFE_DEFAULT
import Foreign.Ptr ( Ptr )
Expand Down
1 change: 1 addition & 0 deletions Foreign/ForeignPtr/Imp.hs
@@ -1,3 +1,4 @@
{-# LANGUAGE Unsafe #-}
{-# LANGUAGE CPP, NoImplicitPrelude #-}
{-# OPTIONS_HADDOCK hide #-}

Expand Down
2 changes: 1 addition & 1 deletion Foreign/ForeignPtr/Unsafe.hs
@@ -1,4 +1,4 @@
{-# LANGUAGE Trustworthy #-}
{-# LANGUAGE Unsafe #-}
{-# LANGUAGE CPP, NoImplicitPrelude #-}

-----------------------------------------------------------------------------
Expand Down
1 change: 1 addition & 0 deletions Foreign/Marshal.hs
@@ -1,3 +1,4 @@
{-# LANGUAGE Unsafe #-}
{-# LANGUAGE CPP, NoImplicitPrelude #-}

-----------------------------------------------------------------------------
Expand Down
2 changes: 1 addition & 1 deletion Foreign/Marshal/Unsafe.hs
@@ -1,4 +1,4 @@
{-# LANGUAGE Trustworthy #-}
{-# LANGUAGE Unsafe #-}
{-# LANGUAGE CPP, NoImplicitPrelude #-}

-----------------------------------------------------------------------------
Expand Down
1 change: 1 addition & 0 deletions GHC/Arr.lhs
@@ -1,4 +1,5 @@
\begin{code}
{-# LANGUAGE Unsafe #-}
{-# LANGUAGE NoImplicitPrelude, NoBangPatterns, MagicHash, UnboxedTuples #-}
{-# OPTIONS_GHC -funbox-strict-fields #-}
{-# OPTIONS_HADDOCK hide #-}
Expand Down
1 change: 1 addition & 0 deletions GHC/Base.lhs
Expand Up @@ -62,6 +62,7 @@ GHC.Float Classes: Floating, RealFloat
Other Prelude modules are much easier with fewer complex dependencies.

\begin{code}
{-# LANGUAGE Unsafe #-}
{-# LANGUAGE CPP
, NoImplicitPrelude
, BangPatterns
Expand Down
1 change: 1 addition & 0 deletions GHC/Conc.lhs
@@ -1,4 +1,5 @@
\begin{code}
{-# LANGUAGE Unsafe #-}
{-# LANGUAGE CPP, NoImplicitPrelude #-}
{-# OPTIONS_GHC -fno-warn-missing-signatures #-}
{-# OPTIONS_HADDOCK not-home #-}
Expand Down
1 change: 1 addition & 0 deletions GHC/Conc/IO.hs
@@ -1,3 +1,4 @@
{-# LANGUAGE Unsafe #-}
{-# LANGUAGE CPP
, NoImplicitPrelude
, MagicHash
Expand Down
1 change: 1 addition & 0 deletions GHC/Conc/Sync.lhs
@@ -1,4 +1,5 @@
\begin{code}
{-# LANGUAGE Unsafe #-}
{-# LANGUAGE CPP
, NoImplicitPrelude
, BangPatterns
Expand Down
1 change: 1 addition & 0 deletions GHC/Conc/Windows.hs
@@ -1,3 +1,4 @@
{-# LANGUAGE Unsafe #-}
{-# LANGUAGE NoImplicitPrelude, MagicHash, UnboxedTuples, ForeignFunctionInterface,
DeriveDataTypeable #-}
{-# OPTIONS_GHC -fno-warn-missing-signatures #-}
Expand Down
1 change: 1 addition & 0 deletions GHC/Event/Array.hs
@@ -1,3 +1,4 @@
{-# LANGUAGE Unsafe #-}
{-# LANGUAGE BangPatterns, CPP, ForeignFunctionInterface, NoImplicitPrelude #-}

module GHC.Event.Array
Expand Down
1 change: 1 addition & 0 deletions GHC/Event/Clock.hsc
@@ -1,3 +1,4 @@
{-# LANGUAGE Unsafe #-}
{-# LANGUAGE NoImplicitPrelude, BangPatterns, ForeignFunctionInterface #-}

module GHC.Event.Clock (getCurrentTime) where
Expand Down
1 change: 1 addition & 0 deletions GHC/Event/Control.hs
@@ -1,3 +1,4 @@
{-# LANGUAGE Unsafe #-}
{-# LANGUAGE CPP
, ForeignFunctionInterface
, NoImplicitPrelude
Expand Down
1 change: 1 addition & 0 deletions GHC/Event/EPoll.hsc
@@ -1,3 +1,4 @@
{-# LANGUAGE Unsafe #-}
{-# LANGUAGE CPP
, ForeignFunctionInterface
, GeneralizedNewtypeDeriving
Expand Down
1 change: 1 addition & 0 deletions GHC/Event/IntMap.hs
@@ -1,3 +1,4 @@
{-# LANGUAGE Unsafe #-}
{-# LANGUAGE CPP, MagicHash, NoImplicitPrelude #-}

-----------------------------------------------------------------------------
Expand Down
1 change: 1 addition & 0 deletions GHC/Event/Internal.hs
@@ -1,3 +1,4 @@
{-# LANGUAGE Unsafe #-}
{-# LANGUAGE ExistentialQuantification, NoImplicitPrelude #-}

module GHC.Event.Internal
Expand Down
1 change: 1 addition & 0 deletions GHC/Event/KQueue.hsc
@@ -1,3 +1,4 @@
{-# LANGUAGE Unsafe #-}
{-# LANGUAGE CPP
, ForeignFunctionInterface
, GeneralizedNewtypeDeriving
Expand Down
1 change: 1 addition & 0 deletions GHC/Event/Manager.hs
@@ -1,3 +1,4 @@
{-# LANGUAGE Unsafe #-}
{-# LANGUAGE BangPatterns
, CPP
, ExistentialQuantification
Expand Down
1 change: 1 addition & 0 deletions GHC/Event/PSQ.hs
@@ -1,3 +1,4 @@
{-# LANGUAGE Unsafe #-}
{-# LANGUAGE BangPatterns, NoImplicitPrelude #-}

-- Copyright (c) 2008, Ralf Hinze
Expand Down
1 change: 1 addition & 0 deletions GHC/Event/Poll.hsc
@@ -1,3 +1,4 @@
{-# LANGUAGE Unsafe #-}
{-# LANGUAGE CPP
, ForeignFunctionInterface
, GeneralizedNewtypeDeriving
Expand Down
1 change: 1 addition & 0 deletions GHC/Event/Thread.hs
@@ -1,3 +1,4 @@
{-# LANGUAGE Unsafe #-}
{-# LANGUAGE BangPatterns, ForeignFunctionInterface, NoImplicitPrelude #-}

module GHC.Event.Thread
Expand Down
1 change: 1 addition & 0 deletions GHC/Event/Unique.hs
@@ -1,3 +1,4 @@
{-# LANGUAGE Unsafe #-}
{-# LANGUAGE BangPatterns, GeneralizedNewtypeDeriving, NoImplicitPrelude #-}
module GHC.Event.Unique
(
Expand Down
1 change: 1 addition & 0 deletions GHC/Exts.hs
@@ -1,3 +1,4 @@
{-# LANGUAGE Unsafe #-}
{-# LANGUAGE MagicHash, UnboxedTuples, DeriveDataTypeable #-}

-----------------------------------------------------------------------------
Expand Down
1 change: 1 addition & 0 deletions GHC/Fingerprint.hs
@@ -1,3 +1,4 @@
{-# LANGUAGE Unsafe #-}
{-# LANGUAGE NoImplicitPrelude
, BangPatterns
, ForeignFunctionInterface
Expand Down
1 change: 1 addition & 0 deletions GHC/Fingerprint.hs-boot
@@ -1,3 +1,4 @@
{-# LANGUAGE Unsafe #-}
{-# LANGUAGE NoImplicitPrelude #-}
module GHC.Fingerprint (
fingerprintString,
Expand Down
1 change: 1 addition & 0 deletions GHC/Fingerprint/Type.hs
@@ -1,3 +1,4 @@
{-# LANGUAGE Trustworthy #-}
{-# LANGUAGE NoImplicitPrelude #-}
-- ----------------------------------------------------------------------------
--
Expand Down
1 change: 1 addition & 0 deletions GHC/ForeignPtr.hs
@@ -1,3 +1,4 @@
{-# LANGUAGE Unsafe #-}
{-# LANGUAGE CPP
, NoImplicitPrelude
, BangPatterns
Expand Down
1 change: 1 addition & 0 deletions GHC/IO.hs
@@ -1,3 +1,4 @@
{-# LANGUAGE Unsafe #-}
{-# LANGUAGE NoImplicitPrelude
, BangPatterns
, RankNTypes
Expand Down
1 change: 1 addition & 0 deletions GHC/IO.hs-boot
@@ -1,3 +1,4 @@
{-# LANGUAGE Unsafe #-}
{-# LANGUAGE NoImplicitPrelude #-}

module GHC.IO where
Expand Down
1 change: 1 addition & 0 deletions GHC/IO/FD.hs
@@ -1,3 +1,4 @@
{-# LANGUAGE Unsafe #-}
{-# LANGUAGE CPP
, NoImplicitPrelude
, BangPatterns
Expand Down
1 change: 1 addition & 0 deletions GHC/IOArray.hs
@@ -1,3 +1,4 @@
{-# LANGUAGE Unsafe #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# OPTIONS_GHC -funbox-strict-fields #-}
{-# OPTIONS_HADDOCK hide #-}
Expand Down
1 change: 1 addition & 0 deletions GHC/IOBase.hs
@@ -1,3 +1,4 @@
{-# LANGUAGE Unsafe #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# OPTIONS_HADDOCK hide #-}

Expand Down
1 change: 1 addition & 0 deletions GHC/IORef.hs
@@ -1,3 +1,4 @@
{-# LANGUAGE Unsafe #-}
{-# LANGUAGE NoImplicitPrelude, MagicHash #-}
{-# OPTIONS_GHC -funbox-strict-fields #-}
{-# OPTIONS_HADDOCK hide #-}
Expand Down
1 change: 1 addition & 0 deletions GHC/MVar.hs
@@ -1,3 +1,4 @@
{-# LANGUAGE Unsafe #-}
{-# LANGUAGE NoImplicitPrelude, MagicHash, UnboxedTuples #-}
{-# OPTIONS_GHC -funbox-strict-fields #-}
{-# OPTIONS_HADDOCK hide #-}
Expand Down
1 change: 1 addition & 0 deletions GHC/Pack.lhs
@@ -1,4 +1,5 @@
\begin{code}
{-# LANGUAGE Unsafe #-}
{-# LANGUAGE NoImplicitPrelude, MagicHash, UnboxedTuples #-}
{-# OPTIONS_HADDOCK hide #-}
Expand Down
1 change: 1 addition & 0 deletions GHC/Ptr.lhs
@@ -1,4 +1,5 @@
\begin{code}
{-# LANGUAGE Unsafe #-}
{-# LANGUAGE CPP, NoImplicitPrelude, MagicHash #-}
{-# OPTIONS_HADDOCK hide #-}
Expand Down
1 change: 1 addition & 0 deletions GHC/ST.lhs
@@ -1,4 +1,5 @@
\begin{code}
{-# LANGUAGE Unsafe #-}
{-# LANGUAGE NoImplicitPrelude, MagicHash, UnboxedTuples, Rank2Types #-}
{-# OPTIONS_HADDOCK hide #-}
-----------------------------------------------------------------------------
Expand Down
1 change: 1 addition & 0 deletions GHC/STRef.lhs
@@ -1,4 +1,5 @@
\begin{code}
{-# LANGUAGE Unsafe #-}
{-# LANGUAGE NoImplicitPrelude, MagicHash, UnboxedTuples #-}
{-# OPTIONS_HADDOCK hide #-}

Expand Down
1 change: 1 addition & 0 deletions GHC/Stable.lhs
@@ -1,4 +1,5 @@
\begin{code}
{-# LANGUAGE Unsafe #-}
{-# LANGUAGE NoImplicitPrelude
, MagicHash
, UnboxedTuples
Expand Down
1 change: 1 addition & 0 deletions GHC/Stats.hsc
@@ -1,3 +1,4 @@
{-# LANGUAGE Safe #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE ForeignFunctionInterface #-}
{-# LANGUAGE RecordWildCards #-}
Expand Down
1 change: 1 addition & 0 deletions GHC/Weak.lhs
@@ -1,4 +1,5 @@
\begin{code}
{-# LANGUAGE Unsafe #-}
{-# LANGUAGE CPP
, NoImplicitPrelude
, BangPatterns
Expand Down
1 change: 1 addition & 0 deletions System/IO/Unsafe.hs
@@ -1,3 +1,4 @@
{-# LANGUAGE Unsafe #-}
{-# LANGUAGE CPP, NoImplicitPrelude #-}

-----------------------------------------------------------------------------
Expand Down
1 change: 1 addition & 0 deletions Unsafe/Coerce.hs
@@ -1,3 +1,4 @@
{-# LANGUAGE Unsafe #-}
{-# LANGUAGE CPP, NoImplicitPrelude, MagicHash #-}

-----------------------------------------------------------------------------
Expand Down

0 comments on commit 447448a

Please sign in to comment.