{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE Safe #-}
-- |
-- Module       : Data.Text.Encoding.Base64.Error
-- Copyright    : (c) 2019-2020 Emily Pillmore
-- License      : BSD-style
--
-- Maintainer   : Emily Pillmore <emilypi@cohomolo.gy>
-- Stability    : stable
-- Portability  : non-portable
--
-- This module contains the error types raised (not as exceptions!)
-- in the decoding process.
--
module Data.Text.Encoding.Base64.Error
( Base64Error(..)
) where


import Control.DeepSeq (NFData(..))
import Control.Exception (Exception(..))

import Data.Text (Text)

import GHC.Generics

-- | This data type represents the type of decoding errors of
-- various kinds as they pertain to decoding 'Text' values.
-- Namely, to distinguish between decoding errors from opaque
-- unicode exceptions caught in the unicode decoding process.
--
data Base64Error e
  = DecodeError Text
    -- ^ The error associated with decoding failure
    -- as a result of the Base64 decoding process
  | ConversionError e
    -- ^ The error associated with the decoding failure
    -- as a result of the conversion process
  deriving
    ( Base64Error e -> Base64Error e -> Bool
(Base64Error e -> Base64Error e -> Bool)
-> (Base64Error e -> Base64Error e -> Bool) -> Eq (Base64Error e)
forall e. Eq e => Base64Error e -> Base64Error e -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Base64Error e -> Base64Error e -> Bool
$c/= :: forall e. Eq e => Base64Error e -> Base64Error e -> Bool
== :: Base64Error e -> Base64Error e -> Bool
$c== :: forall e. Eq e => Base64Error e -> Base64Error e -> Bool
Eq, Int -> Base64Error e -> ShowS
[Base64Error e] -> ShowS
Base64Error e -> String
(Int -> Base64Error e -> ShowS)
-> (Base64Error e -> String)
-> ([Base64Error e] -> ShowS)
-> Show (Base64Error e)
forall e. Show e => Int -> Base64Error e -> ShowS
forall e. Show e => [Base64Error e] -> ShowS
forall e. Show e => Base64Error e -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Base64Error e] -> ShowS
$cshowList :: forall e. Show e => [Base64Error e] -> ShowS
show :: Base64Error e -> String
$cshow :: forall e. Show e => Base64Error e -> String
showsPrec :: Int -> Base64Error e -> ShowS
$cshowsPrec :: forall e. Show e => Int -> Base64Error e -> ShowS
Show
    , Generic
      -- ^ @since 4.2.2
    )

-- |
--
-- @since 4.2.2
--
instance Exception e => Exception (Base64Error e)


-- |
--
-- @since 4.2.2
--
instance NFData e => NFData (Base64Error e)