Skip to content

Commit

Permalink
Removed unused language extensions.
Browse files Browse the repository at this point in the history
  • Loading branch information
mightybyte committed Sep 28, 2011
1 parent 7a4df56 commit 9c33d7f
Show file tree
Hide file tree
Showing 10 changed files with 4 additions and 57 deletions.
11 changes: 0 additions & 11 deletions src/Snap/Snaplet/Heist.hs
@@ -1,14 +1,3 @@
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE NoMonomorphismRestriction #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE MultiParamTypeClasses #-}

{-|
The Heist snaplet makes it easy to add Heist to your application and use it in
Expand Down
10 changes: 2 additions & 8 deletions src/Snap/Snaplet/HeistNoClass.hs
@@ -1,12 +1,6 @@
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE NoMonomorphismRestriction #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE MultiParamTypeClasses #-}
module Snap.Snaplet.HeistNoClass
( Heist
, heistInit
Expand Down
7 changes: 0 additions & 7 deletions src/Snap/Snaplet/Internal/Initializer.hs
@@ -1,12 +1,5 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE TemplateHaskell #-}

module Snap.Snaplet.Internal.Initializer
( addPostInitHook
Expand Down
3 changes: 0 additions & 3 deletions src/Snap/Snaplet/Internal/LensT.hs
@@ -1,10 +1,7 @@
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE TypeOperators #-}

module Snap.Snaplet.Internal.LensT where

Expand Down
4 changes: 0 additions & 4 deletions src/Snap/Snaplet/Internal/RST.hs
@@ -1,10 +1,6 @@
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE TypeOperators #-}

module Snap.Snaplet.Internal.RST where

Expand Down
6 changes: 0 additions & 6 deletions src/Snap/Snaplet/Internal/Types.hs
@@ -1,14 +1,8 @@
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE NoMonomorphismRestriction #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE FlexibleContexts #-}

module Snap.Snaplet.Internal.Types where
Expand Down
10 changes: 0 additions & 10 deletions src/Snap/Snaplet/Session.hs
@@ -1,7 +1,3 @@
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TypeOperators #-}

module Snap.Snaplet.Session

(
Expand All @@ -18,16 +14,10 @@ module Snap.Snaplet.Session

) where

import Control.Monad.Reader
import Control.Monad.State
import Data.ByteString (ByteString)
import qualified Data.ByteString.Char8 as B
import Data.Lens.Lazy
import Data.Serialize (Serialize)
import Data.Text (Text)

import Snap.Snaplet
import Snap.Snaplet.Session.SecureCookie
import Snap.Core

import Snap.Snaplet.Session.SessionManager
Expand Down
3 changes: 2 additions & 1 deletion src/Snap/Snaplet/Session/Backends/CookieSession.hs
@@ -1,4 +1,5 @@
{-# LANGUAGE DeriveDataTypeable, OverloadedStrings #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}

module Snap.Snaplet.Session.Backends.CookieSession
Expand Down
2 changes: 0 additions & 2 deletions src/Snap/Snaplet/Session/Common.hs
@@ -1,5 +1,3 @@
{-# LANGUAGE ScopedTypeVariables #-}

{-|
This module contains functionality common among multiple back-ends.
Expand Down
5 changes: 0 additions & 5 deletions src/Snap/Snaplet/Session/SessionManager.hs
@@ -1,16 +1,11 @@
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ExistentialQuantification #-}

module Snap.Snaplet.Session.SessionManager where

import Control.Monad.State
import Data.ByteString (ByteString)
import Data.Serialize (Serialize)
import Data.Text (Text)
import Prelude hiding (lookup)

import Snap.Core (Snap)
import Snap.Snaplet


-- | Any Haskell record that is a member of the 'ISessionManager' typeclass can
Expand Down

0 comments on commit 9c33d7f

Please sign in to comment.