Skip to content

Commit

Permalink
dispel redundant import warnings
Browse files Browse the repository at this point in the history
Minimum supported version of GHC moved to 8.8.  Now we can clean up
some old redundant import warnings.
  • Loading branch information
frasertweedale committed Oct 31, 2023
1 parent d853a27 commit b76ce38
Show file tree
Hide file tree
Showing 12 changed files with 0 additions and 13 deletions.
1 change: 0 additions & 1 deletion example/KeyDB.hs
Original file line number Diff line number Diff line change
Expand Up @@ -9,7 +9,6 @@ module KeyDB

import Control.Exception (IOException, handle)
import Data.Maybe (catMaybes)
import Data.Semigroup ((<>))

import Control.Monad.Trans (MonadIO(..))
import Control.Lens (_Just, preview)
Expand Down
1 change: 0 additions & 1 deletion example/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,7 +2,6 @@
{-# LANGUAGE FlexibleContexts #-}

import Data.Maybe (fromJust)
import Data.Semigroup ((<>))
import System.Environment (getArgs)
import System.Exit (die, exitFailure)

Expand Down
1 change: 0 additions & 1 deletion src/Crypto/JOSE/Error.hs
Original file line number Diff line number Diff line change
Expand Up @@ -41,7 +41,6 @@ module Crypto.JOSE.Error

) where

import Data.Semigroup ((<>))
import Numeric.Natural

import Control.Monad.Except (MonadError(..), ExceptT, runExceptT)
Expand Down
1 change: 0 additions & 1 deletion src/Crypto/JOSE/Header.hs
Original file line number Diff line number Diff line change
Expand Up @@ -66,7 +66,6 @@ module Crypto.JOSE.Header
import qualified Control.Monad.Fail as Fail
import Data.Kind (Type)
import Data.List.NonEmpty (NonEmpty)
import Data.Monoid ((<>))
import Data.Proxy (Proxy(..))

import Control.Lens (Lens', Getter, review, to)
Expand Down
1 change: 0 additions & 1 deletion src/Crypto/JOSE/JWA/JWK.hs
Original file line number Diff line number Diff line change
Expand Up @@ -77,7 +77,6 @@ import Control.Monad.Except (MonadError)
import Data.Bifunctor
import Data.Foldable (toList)
import Data.Maybe (isJust)
import Data.Monoid ((<>))

import Control.Lens hiding ((.=), elements)
import Control.Monad.Error.Lens (throwing, throwing_)
Expand Down
1 change: 0 additions & 1 deletion src/Crypto/JOSE/JWE.hs
Original file line number Diff line number Diff line change
Expand Up @@ -27,7 +27,6 @@ module Crypto.JOSE.JWE
import Control.Applicative ((<|>))
import Data.Bifunctor (bimap)
import Data.Maybe (catMaybes, fromMaybe)
import Data.Monoid ((<>))

import Control.Lens (view, views)
import Data.Aeson
Expand Down
1 change: 0 additions & 1 deletion src/Crypto/JOSE/JWK.hs
Original file line number Diff line number Diff line change
Expand Up @@ -92,7 +92,6 @@ import Control.Applicative
import Control.Monad ((>=>))
import Data.Function (on)
import Data.Maybe (catMaybes)
import Data.Monoid ((<>))
import Data.Word (Word8)

import Control.Lens hiding ((.=))
Expand Down
1 change: 0 additions & 1 deletion src/Crypto/JOSE/JWS.hs
Original file line number Diff line number Diff line change
Expand Up @@ -92,7 +92,6 @@ import Control.Applicative ((<|>))
import Control.Monad (unless)
import Data.Foldable (toList)
import Data.Maybe (catMaybes, fromMaybe)
import Data.Monoid ((<>))
import Data.List.NonEmpty (NonEmpty)
import Data.Word (Word8)

Expand Down
1 change: 0 additions & 1 deletion src/Crypto/JWT.hs
Original file line number Diff line number Diff line change
Expand Up @@ -95,7 +95,6 @@ import Data.Foldable (traverse_)
import Data.Functor.Identity
import Data.Maybe
import qualified Data.String
import Data.Semigroup ((<>))

import Control.Lens (
makeClassy, makeClassyPrisms, makePrisms,
Expand Down
2 changes: 0 additions & 2 deletions test/JWK.hs
Original file line number Diff line number Diff line change
Expand Up @@ -19,8 +19,6 @@ module JWK
( spec
) where

import Data.Monoid ((<>))

import Control.Lens (_Left, _Right, review, view)
import Control.Lens.Extras (is)
import Data.Aeson
Expand Down
1 change: 0 additions & 1 deletion test/JWS.hs
Original file line number Diff line number Diff line change
Expand Up @@ -19,7 +19,6 @@ module JWS
) where

import Data.Maybe
import Data.Monoid ((<>))

import Control.Lens hiding ((.=))
import Control.Lens.Extras (is)
Expand Down
1 change: 0 additions & 1 deletion test/JWT.hs
Original file line number Diff line number Diff line change
Expand Up @@ -20,7 +20,6 @@ module JWT
) where

import Data.Maybe
import Data.Monoid ((<>))

import qualified Data.ByteString.Lazy as L
import Control.Lens
Expand Down

0 comments on commit b76ce38

Please sign in to comment.