{-# LANGUAGE CPP                #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric      #-}
{-# LANGUAGE TemplateHaskell    #-}
{-# LANGUAGE TypeFamilies       #-}

#if __GLASGOW_HASKELL__ >= 800
{-# LANGUAGE DeriveLift         #-}
#endif

{-|
Module:      TextShow.Options
Copyright:   (C) 2014-2017 Ryan Scott
License:     BSD-style (see the file LICENSE)
Maintainer:  Ryan Scott
Stability:   Provisional
Portability: GHC

'Options' and related datatypes.

/Since: 3.4/
-}
module TextShow.Options (Options(..), GenTextMethods(..), defaultOptions) where

import Data.Data (Data, Typeable)
import Data.Ix (Ix)

import GHC.Generics (Generic)

import Language.Haskell.TH.Lift

-- | Options that specify how to derive 'TextShow' instances using Template Haskell.
--
-- /Since: 3.4/
data Options = Options
  { Options -> GenTextMethods
genTextMethods :: GenTextMethods
    -- ^ When Template Haskell should generate definitions for methods which
    --   return @Text@?
    --
    --   /Since: 3.4/
  , Options -> Bool
emptyCaseBehavior :: Bool
    -- ^ If 'True', derived instances for empty data types (i.e., ones with
    --   no data constructors) will use the @EmptyCase@ language extension.
    --   If 'False', derived instances will simply use 'seq' instead.
    --   (This has no effect on GHCs before 7.8, since @EmptyCase@ is only
    --   available in 7.8 or later.)
    --
    --   /Since: 3.7/
  } deriving ( Typeable Options
DataType
Constr
Typeable Options
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> Options -> c Options)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c Options)
-> (Options -> Constr)
-> (Options -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c Options))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Options))
-> ((forall b. Data b => b -> b) -> Options -> Options)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> Options -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> Options -> r)
-> (forall u. (forall d. Data d => d -> u) -> Options -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Options -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> Options -> m Options)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Options -> m Options)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Options -> m Options)
-> Data Options
Options -> DataType
Options -> Constr
(forall b. Data b => b -> b) -> Options -> Options
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Options -> c Options
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Options
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Options -> u
forall u. (forall d. Data d => d -> u) -> Options -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Options -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Options -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Options -> m Options
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Options -> m Options
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Options
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Options -> c Options
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Options)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Options)
$cOptions :: Constr
$tOptions :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> Options -> m Options
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Options -> m Options
gmapMp :: (forall d. Data d => d -> m d) -> Options -> m Options
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Options -> m Options
gmapM :: (forall d. Data d => d -> m d) -> Options -> m Options
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Options -> m Options
gmapQi :: Int -> (forall d. Data d => d -> u) -> Options -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Options -> u
gmapQ :: (forall d. Data d => d -> u) -> Options -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Options -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Options -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Options -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Options -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Options -> r
gmapT :: (forall b. Data b => b -> b) -> Options -> Options
$cgmapT :: (forall b. Data b => b -> b) -> Options -> Options
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Options)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Options)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c Options)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Options)
dataTypeOf :: Options -> DataType
$cdataTypeOf :: Options -> DataType
toConstr :: Options -> Constr
$ctoConstr :: Options -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Options
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Options
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Options -> c Options
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Options -> c Options
$cp1Data :: Typeable Options
Data
             , Options -> Options -> Bool
(Options -> Options -> Bool)
-> (Options -> Options -> Bool) -> Eq Options
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Options -> Options -> Bool
$c/= :: Options -> Options -> Bool
== :: Options -> Options -> Bool
$c== :: Options -> Options -> Bool
Eq
             , (forall x. Options -> Rep Options x)
-> (forall x. Rep Options x -> Options) -> Generic Options
forall x. Rep Options x -> Options
forall x. Options -> Rep Options x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Options x -> Options
$cfrom :: forall x. Options -> Rep Options x
Generic
             , Eq Options
Eq Options
-> (Options -> Options -> Ordering)
-> (Options -> Options -> Bool)
-> (Options -> Options -> Bool)
-> (Options -> Options -> Bool)
-> (Options -> Options -> Bool)
-> (Options -> Options -> Options)
-> (Options -> Options -> Options)
-> Ord Options
Options -> Options -> Bool
Options -> Options -> Ordering
Options -> Options -> Options
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Options -> Options -> Options
$cmin :: Options -> Options -> Options
max :: Options -> Options -> Options
$cmax :: Options -> Options -> Options
>= :: Options -> Options -> Bool
$c>= :: Options -> Options -> Bool
> :: Options -> Options -> Bool
$c> :: Options -> Options -> Bool
<= :: Options -> Options -> Bool
$c<= :: Options -> Options -> Bool
< :: Options -> Options -> Bool
$c< :: Options -> Options -> Bool
compare :: Options -> Options -> Ordering
$ccompare :: Options -> Options -> Ordering
$cp1Ord :: Eq Options
Ord
             , ReadPrec [Options]
ReadPrec Options
Int -> ReadS Options
ReadS [Options]
(Int -> ReadS Options)
-> ReadS [Options]
-> ReadPrec Options
-> ReadPrec [Options]
-> Read Options
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Options]
$creadListPrec :: ReadPrec [Options]
readPrec :: ReadPrec Options
$creadPrec :: ReadPrec Options
readList :: ReadS [Options]
$creadList :: ReadS [Options]
readsPrec :: Int -> ReadS Options
$creadsPrec :: Int -> ReadS Options
Read
             , Int -> Options -> ShowS
[Options] -> ShowS
Options -> String
(Int -> Options -> ShowS)
-> (Options -> String) -> ([Options] -> ShowS) -> Show Options
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Options] -> ShowS
$cshowList :: [Options] -> ShowS
show :: Options -> String
$cshow :: Options -> String
showsPrec :: Int -> Options -> ShowS
$cshowsPrec :: Int -> Options -> ShowS
Show
             , Typeable
#if __GLASGOW_HASKELL__ >= 800
             , Options -> Q Exp
Options -> Q (TExp Options)
(Options -> Q Exp) -> (Options -> Q (TExp Options)) -> Lift Options
forall t. (t -> Q Exp) -> (t -> Q (TExp t)) -> Lift t
liftTyped :: Options -> Q (TExp Options)
$cliftTyped :: Options -> Q (TExp Options)
lift :: Options -> Q Exp
$clift :: Options -> Q Exp
Lift
#endif
             )

-- | When should Template Haskell generate implementations for the methods of
-- 'TextShow' which return @Text@?
--
-- /Since: 3.4/
data GenTextMethods
  = AlwaysTextMethods    -- ^ Always generate them.
  | SometimesTextMethods -- ^ Only generate when @text-show@ feels it's appropriate.
  | NeverTextMethods     -- ^ Never generate them under any circumstances.
  deriving ( GenTextMethods
GenTextMethods -> GenTextMethods -> Bounded GenTextMethods
forall a. a -> a -> Bounded a
maxBound :: GenTextMethods
$cmaxBound :: GenTextMethods
minBound :: GenTextMethods
$cminBound :: GenTextMethods
Bounded
           , Typeable GenTextMethods
DataType
Constr
Typeable GenTextMethods
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> GenTextMethods -> c GenTextMethods)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c GenTextMethods)
-> (GenTextMethods -> Constr)
-> (GenTextMethods -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c GenTextMethods))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e))
    -> Maybe (c GenTextMethods))
-> ((forall b. Data b => b -> b)
    -> GenTextMethods -> GenTextMethods)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> GenTextMethods -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> GenTextMethods -> r)
-> (forall u.
    (forall d. Data d => d -> u) -> GenTextMethods -> [u])
-> (forall u.
    Int -> (forall d. Data d => d -> u) -> GenTextMethods -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d)
    -> GenTextMethods -> m GenTextMethods)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d)
    -> GenTextMethods -> m GenTextMethods)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d)
    -> GenTextMethods -> m GenTextMethods)
-> Data GenTextMethods
GenTextMethods -> DataType
GenTextMethods -> Constr
(forall b. Data b => b -> b) -> GenTextMethods -> GenTextMethods
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> GenTextMethods -> c GenTextMethods
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c GenTextMethods
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int -> (forall d. Data d => d -> u) -> GenTextMethods -> u
forall u. (forall d. Data d => d -> u) -> GenTextMethods -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> GenTextMethods -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> GenTextMethods -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> GenTextMethods -> m GenTextMethods
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> GenTextMethods -> m GenTextMethods
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c GenTextMethods
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> GenTextMethods -> c GenTextMethods
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c GenTextMethods)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c GenTextMethods)
$cNeverTextMethods :: Constr
$cSometimesTextMethods :: Constr
$cAlwaysTextMethods :: Constr
$tGenTextMethods :: DataType
gmapMo :: (forall d. Data d => d -> m d)
-> GenTextMethods -> m GenTextMethods
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> GenTextMethods -> m GenTextMethods
gmapMp :: (forall d. Data d => d -> m d)
-> GenTextMethods -> m GenTextMethods
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> GenTextMethods -> m GenTextMethods
gmapM :: (forall d. Data d => d -> m d)
-> GenTextMethods -> m GenTextMethods
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> GenTextMethods -> m GenTextMethods
gmapQi :: Int -> (forall d. Data d => d -> u) -> GenTextMethods -> u
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> GenTextMethods -> u
gmapQ :: (forall d. Data d => d -> u) -> GenTextMethods -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> GenTextMethods -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> GenTextMethods -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> GenTextMethods -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> GenTextMethods -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> GenTextMethods -> r
gmapT :: (forall b. Data b => b -> b) -> GenTextMethods -> GenTextMethods
$cgmapT :: (forall b. Data b => b -> b) -> GenTextMethods -> GenTextMethods
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c GenTextMethods)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c GenTextMethods)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c GenTextMethods)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c GenTextMethods)
dataTypeOf :: GenTextMethods -> DataType
$cdataTypeOf :: GenTextMethods -> DataType
toConstr :: GenTextMethods -> Constr
$ctoConstr :: GenTextMethods -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c GenTextMethods
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c GenTextMethods
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> GenTextMethods -> c GenTextMethods
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> GenTextMethods -> c GenTextMethods
$cp1Data :: Typeable GenTextMethods
Data
           , Int -> GenTextMethods
GenTextMethods -> Int
GenTextMethods -> [GenTextMethods]
GenTextMethods -> GenTextMethods
GenTextMethods -> GenTextMethods -> [GenTextMethods]
GenTextMethods
-> GenTextMethods -> GenTextMethods -> [GenTextMethods]
(GenTextMethods -> GenTextMethods)
-> (GenTextMethods -> GenTextMethods)
-> (Int -> GenTextMethods)
-> (GenTextMethods -> Int)
-> (GenTextMethods -> [GenTextMethods])
-> (GenTextMethods -> GenTextMethods -> [GenTextMethods])
-> (GenTextMethods -> GenTextMethods -> [GenTextMethods])
-> (GenTextMethods
    -> GenTextMethods -> GenTextMethods -> [GenTextMethods])
-> Enum GenTextMethods
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: GenTextMethods
-> GenTextMethods -> GenTextMethods -> [GenTextMethods]
$cenumFromThenTo :: GenTextMethods
-> GenTextMethods -> GenTextMethods -> [GenTextMethods]
enumFromTo :: GenTextMethods -> GenTextMethods -> [GenTextMethods]
$cenumFromTo :: GenTextMethods -> GenTextMethods -> [GenTextMethods]
enumFromThen :: GenTextMethods -> GenTextMethods -> [GenTextMethods]
$cenumFromThen :: GenTextMethods -> GenTextMethods -> [GenTextMethods]
enumFrom :: GenTextMethods -> [GenTextMethods]
$cenumFrom :: GenTextMethods -> [GenTextMethods]
fromEnum :: GenTextMethods -> Int
$cfromEnum :: GenTextMethods -> Int
toEnum :: Int -> GenTextMethods
$ctoEnum :: Int -> GenTextMethods
pred :: GenTextMethods -> GenTextMethods
$cpred :: GenTextMethods -> GenTextMethods
succ :: GenTextMethods -> GenTextMethods
$csucc :: GenTextMethods -> GenTextMethods
Enum
           , GenTextMethods -> GenTextMethods -> Bool
(GenTextMethods -> GenTextMethods -> Bool)
-> (GenTextMethods -> GenTextMethods -> Bool) -> Eq GenTextMethods
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GenTextMethods -> GenTextMethods -> Bool
$c/= :: GenTextMethods -> GenTextMethods -> Bool
== :: GenTextMethods -> GenTextMethods -> Bool
$c== :: GenTextMethods -> GenTextMethods -> Bool
Eq
           , (forall x. GenTextMethods -> Rep GenTextMethods x)
-> (forall x. Rep GenTextMethods x -> GenTextMethods)
-> Generic GenTextMethods
forall x. Rep GenTextMethods x -> GenTextMethods
forall x. GenTextMethods -> Rep GenTextMethods x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GenTextMethods x -> GenTextMethods
$cfrom :: forall x. GenTextMethods -> Rep GenTextMethods x
Generic
           , Ord GenTextMethods
Ord GenTextMethods
-> ((GenTextMethods, GenTextMethods) -> [GenTextMethods])
-> ((GenTextMethods, GenTextMethods) -> GenTextMethods -> Int)
-> ((GenTextMethods, GenTextMethods) -> GenTextMethods -> Int)
-> ((GenTextMethods, GenTextMethods) -> GenTextMethods -> Bool)
-> ((GenTextMethods, GenTextMethods) -> Int)
-> ((GenTextMethods, GenTextMethods) -> Int)
-> Ix GenTextMethods
(GenTextMethods, GenTextMethods) -> Int
(GenTextMethods, GenTextMethods) -> [GenTextMethods]
(GenTextMethods, GenTextMethods) -> GenTextMethods -> Bool
(GenTextMethods, GenTextMethods) -> GenTextMethods -> Int
forall a.
Ord a
-> ((a, a) -> [a])
-> ((a, a) -> a -> Int)
-> ((a, a) -> a -> Int)
-> ((a, a) -> a -> Bool)
-> ((a, a) -> Int)
-> ((a, a) -> Int)
-> Ix a
unsafeRangeSize :: (GenTextMethods, GenTextMethods) -> Int
$cunsafeRangeSize :: (GenTextMethods, GenTextMethods) -> Int
rangeSize :: (GenTextMethods, GenTextMethods) -> Int
$crangeSize :: (GenTextMethods, GenTextMethods) -> Int
inRange :: (GenTextMethods, GenTextMethods) -> GenTextMethods -> Bool
$cinRange :: (GenTextMethods, GenTextMethods) -> GenTextMethods -> Bool
unsafeIndex :: (GenTextMethods, GenTextMethods) -> GenTextMethods -> Int
$cunsafeIndex :: (GenTextMethods, GenTextMethods) -> GenTextMethods -> Int
index :: (GenTextMethods, GenTextMethods) -> GenTextMethods -> Int
$cindex :: (GenTextMethods, GenTextMethods) -> GenTextMethods -> Int
range :: (GenTextMethods, GenTextMethods) -> [GenTextMethods]
$crange :: (GenTextMethods, GenTextMethods) -> [GenTextMethods]
$cp1Ix :: Ord GenTextMethods
Ix
           , Eq GenTextMethods
Eq GenTextMethods
-> (GenTextMethods -> GenTextMethods -> Ordering)
-> (GenTextMethods -> GenTextMethods -> Bool)
-> (GenTextMethods -> GenTextMethods -> Bool)
-> (GenTextMethods -> GenTextMethods -> Bool)
-> (GenTextMethods -> GenTextMethods -> Bool)
-> (GenTextMethods -> GenTextMethods -> GenTextMethods)
-> (GenTextMethods -> GenTextMethods -> GenTextMethods)
-> Ord GenTextMethods
GenTextMethods -> GenTextMethods -> Bool
GenTextMethods -> GenTextMethods -> Ordering
GenTextMethods -> GenTextMethods -> GenTextMethods
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: GenTextMethods -> GenTextMethods -> GenTextMethods
$cmin :: GenTextMethods -> GenTextMethods -> GenTextMethods
max :: GenTextMethods -> GenTextMethods -> GenTextMethods
$cmax :: GenTextMethods -> GenTextMethods -> GenTextMethods
>= :: GenTextMethods -> GenTextMethods -> Bool
$c>= :: GenTextMethods -> GenTextMethods -> Bool
> :: GenTextMethods -> GenTextMethods -> Bool
$c> :: GenTextMethods -> GenTextMethods -> Bool
<= :: GenTextMethods -> GenTextMethods -> Bool
$c<= :: GenTextMethods -> GenTextMethods -> Bool
< :: GenTextMethods -> GenTextMethods -> Bool
$c< :: GenTextMethods -> GenTextMethods -> Bool
compare :: GenTextMethods -> GenTextMethods -> Ordering
$ccompare :: GenTextMethods -> GenTextMethods -> Ordering
$cp1Ord :: Eq GenTextMethods
Ord
           , ReadPrec [GenTextMethods]
ReadPrec GenTextMethods
Int -> ReadS GenTextMethods
ReadS [GenTextMethods]
(Int -> ReadS GenTextMethods)
-> ReadS [GenTextMethods]
-> ReadPrec GenTextMethods
-> ReadPrec [GenTextMethods]
-> Read GenTextMethods
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GenTextMethods]
$creadListPrec :: ReadPrec [GenTextMethods]
readPrec :: ReadPrec GenTextMethods
$creadPrec :: ReadPrec GenTextMethods
readList :: ReadS [GenTextMethods]
$creadList :: ReadS [GenTextMethods]
readsPrec :: Int -> ReadS GenTextMethods
$creadsPrec :: Int -> ReadS GenTextMethods
Read
           , Int -> GenTextMethods -> ShowS
[GenTextMethods] -> ShowS
GenTextMethods -> String
(Int -> GenTextMethods -> ShowS)
-> (GenTextMethods -> String)
-> ([GenTextMethods] -> ShowS)
-> Show GenTextMethods
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GenTextMethods] -> ShowS
$cshowList :: [GenTextMethods] -> ShowS
show :: GenTextMethods -> String
$cshow :: GenTextMethods -> String
showsPrec :: Int -> GenTextMethods -> ShowS
$cshowsPrec :: Int -> GenTextMethods -> ShowS
Show
           , Typeable
#if __GLASGOW_HASKELL__ >= 800
           , GenTextMethods -> Q Exp
GenTextMethods -> Q (TExp GenTextMethods)
(GenTextMethods -> Q Exp)
-> (GenTextMethods -> Q (TExp GenTextMethods))
-> Lift GenTextMethods
forall t. (t -> Q Exp) -> (t -> Q (TExp t)) -> Lift t
liftTyped :: GenTextMethods -> Q (TExp GenTextMethods)
$cliftTyped :: GenTextMethods -> Q (TExp GenTextMethods)
lift :: GenTextMethods -> Q Exp
$clift :: GenTextMethods -> Q Exp
Lift
#endif
           )

-- | Sensible default 'Options'.
--
-- /Since: 3.4/
defaultOptions :: Options
defaultOptions :: Options
defaultOptions =
  Options :: GenTextMethods -> Bool -> Options
Options { genTextMethods :: GenTextMethods
genTextMethods    = GenTextMethods
SometimesTextMethods
          , emptyCaseBehavior :: Bool
emptyCaseBehavior = Bool
False
          }

-------------------------------------------------------------------------------

#if __GLASGOW_HASKELL__ < 800
$(deriveLift ''Options)
$(deriveLift ''GenTextMethods)
#endif