{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveFoldable #-}
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DeriveTraversable #-}
{-# LANGUAGE EmptyCase #-}
{-# LANGUAGE EmptyDataDecls #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeSynonymInstances #-}
{-# LANGUAGE UndecidableInstances #-}
#if __GLASGOW_HASKELL__ >= 800
{-# LANGUAGE DeriveLift #-}
#endif
#if __GLASGOW_HASKELL__ >= 806
{-# LANGUAGE QuantifiedConstraints #-}
#endif
module TextShow.Generic (
FromGeneric(..)
, FromGeneric1(..)
, genericShowt
, genericShowtl
, genericShowtPrec
, genericShowtlPrec
, genericShowtList
, genericShowtlList
, genericShowb
, genericShowbPrec
, genericShowbList
, genericPrintT
, genericPrintTL
, genericHPrintT
, genericHPrintTL
, genericLiftShowbPrec
, genericShowbPrec1
, GTextShowB(..)
, GTextShowConB(..)
, GTextShowB1(..)
, GTextShowConB1(..)
, GTextShowT(..)
, GTextShowConT(..)
, GTextShowT1(..)
, GTextShowConT1(..)
, GTextShowTL(..)
, GTextShowConTL(..)
, GTextShowTL1(..)
, GTextShowConTL1(..)
, IsNullary(..)
, ConType(..)
) where
import Data.Data (Data, Typeable)
import qualified Data.Text as TS (Text, pack, singleton)
import qualified Data.Text.IO as TS (putStrLn, hPutStrLn)
import qualified Data.Text.Lazy as TL (Text, pack, singleton)
import qualified Data.Text.Lazy.IO as TL (putStrLn, hPutStrLn)
import qualified Data.Text.Lazy.Builder as TB (fromString, singleton)
import Data.Text.Lazy.Builder (Builder)
import Generics.Deriving.Base
#if !defined(__LANGUAGE_DERIVE_GENERIC1__)
import qualified Generics.Deriving.TH as Generics
#endif
import GHC.Exts (Char(C#), Double(D#), Float(F#), Int(I#), Word(W#))
import GHC.Show (appPrec, appPrec1)
import Language.Haskell.TH.Lift
import Prelude ()
import Prelude.Compat
import System.IO (Handle)
import TextShow.Classes (TextShow(..), TextShow1(..),
showbListWith, showbParen, showbSpace,
showtListWith, showtParen, showtSpace,
showtlListWith, showtlParen, showtlSpace,
liftShowtPrec, liftShowtlPrec)
import TextShow.Instances ()
import TextShow.TH.Internal (deriveTextShow)
import TextShow.Utils (isInfixDataCon, isSymVar, isTupleString)
newtype FromGeneric a = FromGeneric { forall a. FromGeneric a -> a
fromGeneric :: a }
deriving ( Typeable (FromGeneric a)
Typeable (FromGeneric a) =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> FromGeneric a -> c (FromGeneric a))
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (FromGeneric a))
-> (FromGeneric a -> Constr)
-> (FromGeneric a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (FromGeneric a)))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (FromGeneric a)))
-> ((forall b. Data b => b -> b) -> FromGeneric a -> FromGeneric a)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> FromGeneric a -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> FromGeneric a -> r)
-> (forall u. (forall d. Data d => d -> u) -> FromGeneric a -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> FromGeneric a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> FromGeneric a -> m (FromGeneric a))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> FromGeneric a -> m (FromGeneric a))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> FromGeneric a -> m (FromGeneric a))
-> Data (FromGeneric a)
FromGeneric a -> Constr
FromGeneric a -> DataType
(forall b. Data b => b -> b) -> FromGeneric a -> FromGeneric a
forall a. Data a => Typeable (FromGeneric a)
forall a. Data a => FromGeneric a -> Constr
forall a. Data a => FromGeneric a -> DataType
forall a.
Data a =>
(forall b. Data b => b -> b) -> FromGeneric a -> FromGeneric a
forall a u.
Data a =>
Int -> (forall d. Data d => d -> u) -> FromGeneric a -> u
forall a u.
Data a =>
(forall d. Data d => d -> u) -> FromGeneric a -> [u]
forall a r r'.
Data a =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> FromGeneric a -> r
forall a r r'.
Data a =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> FromGeneric a -> r
forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d)
-> FromGeneric a -> m (FromGeneric a)
forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> FromGeneric a -> m (FromGeneric a)
forall a (c :: * -> *).
Data a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (FromGeneric a)
forall a (c :: * -> *).
Data a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> FromGeneric a -> c (FromGeneric a)
forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (FromGeneric a))
forall a (t :: * -> * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (FromGeneric a))
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) -> FromGeneric a -> u
forall u. (forall d. Data d => d -> u) -> FromGeneric a -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> FromGeneric a -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> FromGeneric a -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> FromGeneric a -> m (FromGeneric a)
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> FromGeneric a -> m (FromGeneric a)
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (FromGeneric a)
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> FromGeneric a -> c (FromGeneric a)
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (FromGeneric a))
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (FromGeneric a))
$cgfoldl :: forall a (c :: * -> *).
Data a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> FromGeneric a -> c (FromGeneric a)
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> FromGeneric a -> c (FromGeneric a)
$cgunfold :: forall a (c :: * -> *).
Data a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (FromGeneric a)
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (FromGeneric a)
$ctoConstr :: forall a. Data a => FromGeneric a -> Constr
toConstr :: FromGeneric a -> Constr
$cdataTypeOf :: forall a. Data a => FromGeneric a -> DataType
dataTypeOf :: FromGeneric a -> DataType
$cdataCast1 :: forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (FromGeneric a))
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (FromGeneric a))
$cdataCast2 :: forall a (t :: * -> * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (FromGeneric a))
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (FromGeneric a))
$cgmapT :: forall a.
Data a =>
(forall b. Data b => b -> b) -> FromGeneric a -> FromGeneric a
gmapT :: (forall b. Data b => b -> b) -> FromGeneric a -> FromGeneric a
$cgmapQl :: forall a r r'.
Data a =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> FromGeneric a -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> FromGeneric a -> r
$cgmapQr :: forall a r r'.
Data a =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> FromGeneric a -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> FromGeneric a -> r
$cgmapQ :: forall a u.
Data a =>
(forall d. Data d => d -> u) -> FromGeneric a -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> FromGeneric a -> [u]
$cgmapQi :: forall a u.
Data a =>
Int -> (forall d. Data d => d -> u) -> FromGeneric a -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> FromGeneric a -> u
$cgmapM :: forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d)
-> FromGeneric a -> m (FromGeneric a)
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> FromGeneric a -> m (FromGeneric a)
$cgmapMp :: forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> FromGeneric a -> m (FromGeneric a)
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> FromGeneric a -> m (FromGeneric a)
$cgmapMo :: forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> FromGeneric a -> m (FromGeneric a)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> FromGeneric a -> m (FromGeneric a)
Data
, FromGeneric a -> FromGeneric a -> Bool
(FromGeneric a -> FromGeneric a -> Bool)
-> (FromGeneric a -> FromGeneric a -> Bool) -> Eq (FromGeneric a)
forall a. Eq a => FromGeneric a -> FromGeneric a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall a. Eq a => FromGeneric a -> FromGeneric a -> Bool
== :: FromGeneric a -> FromGeneric a -> Bool
$c/= :: forall a. Eq a => FromGeneric a -> FromGeneric a -> Bool
/= :: FromGeneric a -> FromGeneric a -> Bool
Eq
, (forall m. Monoid m => FromGeneric m -> m)
-> (forall m a. Monoid m => (a -> m) -> FromGeneric a -> m)
-> (forall m a. Monoid m => (a -> m) -> FromGeneric a -> m)
-> (forall a b. (a -> b -> b) -> b -> FromGeneric a -> b)
-> (forall a b. (a -> b -> b) -> b -> FromGeneric a -> b)
-> (forall b a. (b -> a -> b) -> b -> FromGeneric a -> b)
-> (forall b a. (b -> a -> b) -> b -> FromGeneric a -> b)
-> (forall a. (a -> a -> a) -> FromGeneric a -> a)
-> (forall a. (a -> a -> a) -> FromGeneric a -> a)
-> (forall a. FromGeneric a -> [a])
-> (forall a. FromGeneric a -> Bool)
-> (forall a. FromGeneric a -> Int)
-> (forall a. Eq a => a -> FromGeneric a -> Bool)
-> (forall a. Ord a => FromGeneric a -> a)
-> (forall a. Ord a => FromGeneric a -> a)
-> (forall a. Num a => FromGeneric a -> a)
-> (forall a. Num a => FromGeneric a -> a)
-> Foldable FromGeneric
forall a. Eq a => a -> FromGeneric a -> Bool
forall a. Num a => FromGeneric a -> a
forall a. Ord a => FromGeneric a -> a
forall m. Monoid m => FromGeneric m -> m
forall a. FromGeneric a -> Bool
forall a. FromGeneric a -> Int
forall a. FromGeneric a -> [a]
forall a. (a -> a -> a) -> FromGeneric a -> a
forall m a. Monoid m => (a -> m) -> FromGeneric a -> m
forall b a. (b -> a -> b) -> b -> FromGeneric a -> b
forall a b. (a -> b -> b) -> b -> FromGeneric a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> Int)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
$cfold :: forall m. Monoid m => FromGeneric m -> m
fold :: forall m. Monoid m => FromGeneric m -> m
$cfoldMap :: forall m a. Monoid m => (a -> m) -> FromGeneric a -> m
foldMap :: forall m a. Monoid m => (a -> m) -> FromGeneric a -> m
$cfoldMap' :: forall m a. Monoid m => (a -> m) -> FromGeneric a -> m
foldMap' :: forall m a. Monoid m => (a -> m) -> FromGeneric a -> m
$cfoldr :: forall a b. (a -> b -> b) -> b -> FromGeneric a -> b
foldr :: forall a b. (a -> b -> b) -> b -> FromGeneric a -> b
$cfoldr' :: forall a b. (a -> b -> b) -> b -> FromGeneric a -> b
foldr' :: forall a b. (a -> b -> b) -> b -> FromGeneric a -> b
$cfoldl :: forall b a. (b -> a -> b) -> b -> FromGeneric a -> b
foldl :: forall b a. (b -> a -> b) -> b -> FromGeneric a -> b
$cfoldl' :: forall b a. (b -> a -> b) -> b -> FromGeneric a -> b
foldl' :: forall b a. (b -> a -> b) -> b -> FromGeneric a -> b
$cfoldr1 :: forall a. (a -> a -> a) -> FromGeneric a -> a
foldr1 :: forall a. (a -> a -> a) -> FromGeneric a -> a
$cfoldl1 :: forall a. (a -> a -> a) -> FromGeneric a -> a
foldl1 :: forall a. (a -> a -> a) -> FromGeneric a -> a
$ctoList :: forall a. FromGeneric a -> [a]
toList :: forall a. FromGeneric a -> [a]
$cnull :: forall a. FromGeneric a -> Bool
null :: forall a. FromGeneric a -> Bool
$clength :: forall a. FromGeneric a -> Int
length :: forall a. FromGeneric a -> Int
$celem :: forall a. Eq a => a -> FromGeneric a -> Bool
elem :: forall a. Eq a => a -> FromGeneric a -> Bool
$cmaximum :: forall a. Ord a => FromGeneric a -> a
maximum :: forall a. Ord a => FromGeneric a -> a
$cminimum :: forall a. Ord a => FromGeneric a -> a
minimum :: forall a. Ord a => FromGeneric a -> a
$csum :: forall a. Num a => FromGeneric a -> a
sum :: forall a. Num a => FromGeneric a -> a
$cproduct :: forall a. Num a => FromGeneric a -> a
product :: forall a. Num a => FromGeneric a -> a
Foldable
, (forall a b. (a -> b) -> FromGeneric a -> FromGeneric b)
-> (forall a b. a -> FromGeneric b -> FromGeneric a)
-> Functor FromGeneric
forall a b. a -> FromGeneric b -> FromGeneric a
forall a b. (a -> b) -> FromGeneric a -> FromGeneric b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
$cfmap :: forall a b. (a -> b) -> FromGeneric a -> FromGeneric b
fmap :: forall a b. (a -> b) -> FromGeneric a -> FromGeneric b
$c<$ :: forall a b. a -> FromGeneric b -> FromGeneric a
<$ :: forall a b. a -> FromGeneric b -> FromGeneric a
Functor
, (forall x. FromGeneric a -> Rep (FromGeneric a) x)
-> (forall x. Rep (FromGeneric a) x -> FromGeneric a)
-> Generic (FromGeneric a)
forall x. Rep (FromGeneric a) x -> FromGeneric a
forall x. FromGeneric a -> Rep (FromGeneric a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x. Rep (FromGeneric a) x -> FromGeneric a
forall a x. FromGeneric a -> Rep (FromGeneric a) x
$cfrom :: forall a x. FromGeneric a -> Rep (FromGeneric a) x
from :: forall x. FromGeneric a -> Rep (FromGeneric a) x
$cto :: forall a x. Rep (FromGeneric a) x -> FromGeneric a
to :: forall x. Rep (FromGeneric a) x -> FromGeneric a
Generic
, (forall a. FromGeneric a -> Rep1 FromGeneric a)
-> (forall a. Rep1 FromGeneric a -> FromGeneric a)
-> Generic1 FromGeneric
forall a. Rep1 FromGeneric a -> FromGeneric a
forall a. FromGeneric a -> Rep1 FromGeneric a
forall k (f :: k -> *).
(forall (a :: k). f a -> Rep1 f a)
-> (forall (a :: k). Rep1 f a -> f a) -> Generic1 f
$cfrom1 :: forall a. FromGeneric a -> Rep1 FromGeneric a
from1 :: forall a. FromGeneric a -> Rep1 FromGeneric a
$cto1 :: forall a. Rep1 FromGeneric a -> FromGeneric a
to1 :: forall a. Rep1 FromGeneric a -> FromGeneric a
Generic1
, Eq (FromGeneric a)
Eq (FromGeneric a) =>
(FromGeneric a -> FromGeneric a -> Ordering)
-> (FromGeneric a -> FromGeneric a -> Bool)
-> (FromGeneric a -> FromGeneric a -> Bool)
-> (FromGeneric a -> FromGeneric a -> Bool)
-> (FromGeneric a -> FromGeneric a -> Bool)
-> (FromGeneric a -> FromGeneric a -> FromGeneric a)
-> (FromGeneric a -> FromGeneric a -> FromGeneric a)
-> Ord (FromGeneric a)
FromGeneric a -> FromGeneric a -> Bool
FromGeneric a -> FromGeneric a -> Ordering
FromGeneric a -> FromGeneric a -> FromGeneric a
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
forall a. Ord a => Eq (FromGeneric a)
forall a. Ord a => FromGeneric a -> FromGeneric a -> Bool
forall a. Ord a => FromGeneric a -> FromGeneric a -> Ordering
forall a. Ord a => FromGeneric a -> FromGeneric a -> FromGeneric a
$ccompare :: forall a. Ord a => FromGeneric a -> FromGeneric a -> Ordering
compare :: FromGeneric a -> FromGeneric a -> Ordering
$c< :: forall a. Ord a => FromGeneric a -> FromGeneric a -> Bool
< :: FromGeneric a -> FromGeneric a -> Bool
$c<= :: forall a. Ord a => FromGeneric a -> FromGeneric a -> Bool
<= :: FromGeneric a -> FromGeneric a -> Bool
$c> :: forall a. Ord a => FromGeneric a -> FromGeneric a -> Bool
> :: FromGeneric a -> FromGeneric a -> Bool
$c>= :: forall a. Ord a => FromGeneric a -> FromGeneric a -> Bool
>= :: FromGeneric a -> FromGeneric a -> Bool
$cmax :: forall a. Ord a => FromGeneric a -> FromGeneric a -> FromGeneric a
max :: FromGeneric a -> FromGeneric a -> FromGeneric a
$cmin :: forall a. Ord a => FromGeneric a -> FromGeneric a -> FromGeneric a
min :: FromGeneric a -> FromGeneric a -> FromGeneric a
Ord
, ReadPrec [FromGeneric a]
ReadPrec (FromGeneric a)
Int -> ReadS (FromGeneric a)
ReadS [FromGeneric a]
(Int -> ReadS (FromGeneric a))
-> ReadS [FromGeneric a]
-> ReadPrec (FromGeneric a)
-> ReadPrec [FromGeneric a]
-> Read (FromGeneric a)
forall a. Read a => ReadPrec [FromGeneric a]
forall a. Read a => ReadPrec (FromGeneric a)
forall a. Read a => Int -> ReadS (FromGeneric a)
forall a. Read a => ReadS [FromGeneric a]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: forall a. Read a => Int -> ReadS (FromGeneric a)
readsPrec :: Int -> ReadS (FromGeneric a)
$creadList :: forall a. Read a => ReadS [FromGeneric a]
readList :: ReadS [FromGeneric a]
$creadPrec :: forall a. Read a => ReadPrec (FromGeneric a)
readPrec :: ReadPrec (FromGeneric a)
$creadListPrec :: forall a. Read a => ReadPrec [FromGeneric a]
readListPrec :: ReadPrec [FromGeneric a]
Read
, Int -> FromGeneric a -> ShowS
[FromGeneric a] -> ShowS
FromGeneric a -> String
(Int -> FromGeneric a -> ShowS)
-> (FromGeneric a -> String)
-> ([FromGeneric a] -> ShowS)
-> Show (FromGeneric a)
forall a. Show a => Int -> FromGeneric a -> ShowS
forall a. Show a => [FromGeneric a] -> ShowS
forall a. Show a => FromGeneric a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall a. Show a => Int -> FromGeneric a -> ShowS
showsPrec :: Int -> FromGeneric a -> ShowS
$cshow :: forall a. Show a => FromGeneric a -> String
show :: FromGeneric a -> String
$cshowList :: forall a. Show a => [FromGeneric a] -> ShowS
showList :: [FromGeneric a] -> ShowS
Show
, Functor FromGeneric
Foldable FromGeneric
(Functor FromGeneric, Foldable FromGeneric) =>
(forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> FromGeneric a -> f (FromGeneric b))
-> (forall (f :: * -> *) a.
Applicative f =>
FromGeneric (f a) -> f (FromGeneric a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> FromGeneric a -> m (FromGeneric b))
-> (forall (m :: * -> *) a.
Monad m =>
FromGeneric (m a) -> m (FromGeneric a))
-> Traversable FromGeneric
forall (t :: * -> *).
(Functor t, Foldable t) =>
(forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (m :: * -> *) a.
Monad m =>
FromGeneric (m a) -> m (FromGeneric a)
forall (f :: * -> *) a.
Applicative f =>
FromGeneric (f a) -> f (FromGeneric a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> FromGeneric a -> m (FromGeneric b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> FromGeneric a -> f (FromGeneric b)
$ctraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> FromGeneric a -> f (FromGeneric b)
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> FromGeneric a -> f (FromGeneric b)
$csequenceA :: forall (f :: * -> *) a.
Applicative f =>
FromGeneric (f a) -> f (FromGeneric a)
sequenceA :: forall (f :: * -> *) a.
Applicative f =>
FromGeneric (f a) -> f (FromGeneric a)
$cmapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> FromGeneric a -> m (FromGeneric b)
mapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> FromGeneric a -> m (FromGeneric b)
$csequence :: forall (m :: * -> *) a.
Monad m =>
FromGeneric (m a) -> m (FromGeneric a)
sequence :: forall (m :: * -> *) a.
Monad m =>
FromGeneric (m a) -> m (FromGeneric a)
Traversable
, Typeable
#if __GLASGOW_HASKELL__ >= 800
, (forall (m :: * -> *). Quote m => FromGeneric a -> m Exp)
-> (forall (m :: * -> *).
Quote m =>
FromGeneric a -> Code m (FromGeneric a))
-> Lift (FromGeneric a)
forall a (m :: * -> *). (Lift a, Quote m) => FromGeneric a -> m Exp
forall a (m :: * -> *).
(Lift a, Quote m) =>
FromGeneric a -> Code m (FromGeneric a)
forall t.
(forall (m :: * -> *). Quote m => t -> m Exp)
-> (forall (m :: * -> *). Quote m => t -> Code m t) -> Lift t
forall (m :: * -> *). Quote m => FromGeneric a -> m Exp
forall (m :: * -> *).
Quote m =>
FromGeneric a -> Code m (FromGeneric a)
$clift :: forall a (m :: * -> *). (Lift a, Quote m) => FromGeneric a -> m Exp
lift :: forall (m :: * -> *). Quote m => FromGeneric a -> m Exp
$cliftTyped :: forall a (m :: * -> *).
(Lift a, Quote m) =>
FromGeneric a -> Code m (FromGeneric a)
liftTyped :: forall (m :: * -> *).
Quote m =>
FromGeneric a -> Code m (FromGeneric a)
Lift
#endif
)
instance (Generic a, GTextShowB (Rep a ())) => TextShow (FromGeneric a) where
showbPrec :: Int -> FromGeneric a -> Builder
showbPrec Int
p = Int -> a -> Builder
forall a. (Generic a, GTextShowB (Rep a ())) => Int -> a -> Builder
genericShowbPrec Int
p (a -> Builder) -> (FromGeneric a -> a) -> FromGeneric a -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FromGeneric a -> a
forall a. FromGeneric a -> a
fromGeneric
newtype FromGeneric1 f a = FromGeneric1 { forall {k} (f :: k -> *) (a :: k). FromGeneric1 f a -> f a
fromGeneric1 :: f a }
deriving ( FromGeneric1 f a -> FromGeneric1 f a -> Bool
(FromGeneric1 f a -> FromGeneric1 f a -> Bool)
-> (FromGeneric1 f a -> FromGeneric1 f a -> Bool)
-> Eq (FromGeneric1 f a)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall k (f :: k -> *) (a :: k).
Eq (f a) =>
FromGeneric1 f a -> FromGeneric1 f a -> Bool
$c== :: forall k (f :: k -> *) (a :: k).
Eq (f a) =>
FromGeneric1 f a -> FromGeneric1 f a -> Bool
== :: FromGeneric1 f a -> FromGeneric1 f a -> Bool
$c/= :: forall k (f :: k -> *) (a :: k).
Eq (f a) =>
FromGeneric1 f a -> FromGeneric1 f a -> Bool
/= :: FromGeneric1 f a -> FromGeneric1 f a -> Bool
Eq
, Eq (FromGeneric1 f a)
Eq (FromGeneric1 f a) =>
(FromGeneric1 f a -> FromGeneric1 f a -> Ordering)
-> (FromGeneric1 f a -> FromGeneric1 f a -> Bool)
-> (FromGeneric1 f a -> FromGeneric1 f a -> Bool)
-> (FromGeneric1 f a -> FromGeneric1 f a -> Bool)
-> (FromGeneric1 f a -> FromGeneric1 f a -> Bool)
-> (FromGeneric1 f a -> FromGeneric1 f a -> FromGeneric1 f a)
-> (FromGeneric1 f a -> FromGeneric1 f a -> FromGeneric1 f a)
-> Ord (FromGeneric1 f a)
FromGeneric1 f a -> FromGeneric1 f a -> Bool
FromGeneric1 f a -> FromGeneric1 f a -> Ordering
FromGeneric1 f a -> FromGeneric1 f a -> FromGeneric1 f a
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
forall k (f :: k -> *) (a :: k). Ord (f a) => Eq (FromGeneric1 f a)
forall k (f :: k -> *) (a :: k).
Ord (f a) =>
FromGeneric1 f a -> FromGeneric1 f a -> Bool
forall k (f :: k -> *) (a :: k).
Ord (f a) =>
FromGeneric1 f a -> FromGeneric1 f a -> Ordering
forall k (f :: k -> *) (a :: k).
Ord (f a) =>
FromGeneric1 f a -> FromGeneric1 f a -> FromGeneric1 f a
$ccompare :: forall k (f :: k -> *) (a :: k).
Ord (f a) =>
FromGeneric1 f a -> FromGeneric1 f a -> Ordering
compare :: FromGeneric1 f a -> FromGeneric1 f a -> Ordering
$c< :: forall k (f :: k -> *) (a :: k).
Ord (f a) =>
FromGeneric1 f a -> FromGeneric1 f a -> Bool
< :: FromGeneric1 f a -> FromGeneric1 f a -> Bool
$c<= :: forall k (f :: k -> *) (a :: k).
Ord (f a) =>
FromGeneric1 f a -> FromGeneric1 f a -> Bool
<= :: FromGeneric1 f a -> FromGeneric1 f a -> Bool
$c> :: forall k (f :: k -> *) (a :: k).
Ord (f a) =>
FromGeneric1 f a -> FromGeneric1 f a -> Bool
> :: FromGeneric1 f a -> FromGeneric1 f a -> Bool
$c>= :: forall k (f :: k -> *) (a :: k).
Ord (f a) =>
FromGeneric1 f a -> FromGeneric1 f a -> Bool
>= :: FromGeneric1 f a -> FromGeneric1 f a -> Bool
$cmax :: forall k (f :: k -> *) (a :: k).
Ord (f a) =>
FromGeneric1 f a -> FromGeneric1 f a -> FromGeneric1 f a
max :: FromGeneric1 f a -> FromGeneric1 f a -> FromGeneric1 f a
$cmin :: forall k (f :: k -> *) (a :: k).
Ord (f a) =>
FromGeneric1 f a -> FromGeneric1 f a -> FromGeneric1 f a
min :: FromGeneric1 f a -> FromGeneric1 f a -> FromGeneric1 f a
Ord
, ReadPrec [FromGeneric1 f a]
ReadPrec (FromGeneric1 f a)
Int -> ReadS (FromGeneric1 f a)
ReadS [FromGeneric1 f a]
(Int -> ReadS (FromGeneric1 f a))
-> ReadS [FromGeneric1 f a]
-> ReadPrec (FromGeneric1 f a)
-> ReadPrec [FromGeneric1 f a]
-> Read (FromGeneric1 f a)
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
forall k (f :: k -> *) (a :: k).
Read (f a) =>
ReadPrec [FromGeneric1 f a]
forall k (f :: k -> *) (a :: k).
Read (f a) =>
ReadPrec (FromGeneric1 f a)
forall k (f :: k -> *) (a :: k).
Read (f a) =>
Int -> ReadS (FromGeneric1 f a)
forall k (f :: k -> *) (a :: k).
Read (f a) =>
ReadS [FromGeneric1 f a]
$creadsPrec :: forall k (f :: k -> *) (a :: k).
Read (f a) =>
Int -> ReadS (FromGeneric1 f a)
readsPrec :: Int -> ReadS (FromGeneric1 f a)
$creadList :: forall k (f :: k -> *) (a :: k).
Read (f a) =>
ReadS [FromGeneric1 f a]
readList :: ReadS [FromGeneric1 f a]
$creadPrec :: forall k (f :: k -> *) (a :: k).
Read (f a) =>
ReadPrec (FromGeneric1 f a)
readPrec :: ReadPrec (FromGeneric1 f a)
$creadListPrec :: forall k (f :: k -> *) (a :: k).
Read (f a) =>
ReadPrec [FromGeneric1 f a]
readListPrec :: ReadPrec [FromGeneric1 f a]
Read
, Int -> FromGeneric1 f a -> ShowS
[FromGeneric1 f a] -> ShowS
FromGeneric1 f a -> String
(Int -> FromGeneric1 f a -> ShowS)
-> (FromGeneric1 f a -> String)
-> ([FromGeneric1 f a] -> ShowS)
-> Show (FromGeneric1 f a)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall k (f :: k -> *) (a :: k).
Show (f a) =>
Int -> FromGeneric1 f a -> ShowS
forall k (f :: k -> *) (a :: k).
Show (f a) =>
[FromGeneric1 f a] -> ShowS
forall k (f :: k -> *) (a :: k).
Show (f a) =>
FromGeneric1 f a -> String
$cshowsPrec :: forall k (f :: k -> *) (a :: k).
Show (f a) =>
Int -> FromGeneric1 f a -> ShowS
showsPrec :: Int -> FromGeneric1 f a -> ShowS
$cshow :: forall k (f :: k -> *) (a :: k).
Show (f a) =>
FromGeneric1 f a -> String
show :: FromGeneric1 f a -> String
$cshowList :: forall k (f :: k -> *) (a :: k).
Show (f a) =>
[FromGeneric1 f a] -> ShowS
showList :: [FromGeneric1 f a] -> ShowS
Show
, (forall x. FromGeneric1 f a -> Rep (FromGeneric1 f a) x)
-> (forall x. Rep (FromGeneric1 f a) x -> FromGeneric1 f a)
-> Generic (FromGeneric1 f a)
forall x. Rep (FromGeneric1 f a) x -> FromGeneric1 f a
forall x. FromGeneric1 f a -> Rep (FromGeneric1 f a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall k (f :: k -> *) (a :: k) x.
Rep (FromGeneric1 f a) x -> FromGeneric1 f a
forall k (f :: k -> *) (a :: k) x.
FromGeneric1 f a -> Rep (FromGeneric1 f a) x
$cfrom :: forall k (f :: k -> *) (a :: k) x.
FromGeneric1 f a -> Rep (FromGeneric1 f a) x
from :: forall x. FromGeneric1 f a -> Rep (FromGeneric1 f a) x
$cto :: forall k (f :: k -> *) (a :: k) x.
Rep (FromGeneric1 f a) x -> FromGeneric1 f a
to :: forall x. Rep (FromGeneric1 f a) x -> FromGeneric1 f a
Generic
#if defined(__LANGUAGE_DERIVE_GENERIC1__)
, Generic1
#endif
#if __GLASGOW_HASKELL__ >= 800
, (forall (m :: * -> *). Quote m => FromGeneric1 f a -> m Exp)
-> (forall (m :: * -> *).
Quote m =>
FromGeneric1 f a -> Code m (FromGeneric1 f a))
-> Lift (FromGeneric1 f a)
forall k (f :: k -> *) (a :: k) (m :: * -> *).
(Lift (f a), Quote m) =>
FromGeneric1 f a -> m Exp
forall k (f :: k -> *) (a :: k) (m :: * -> *).
(Lift (f a), Quote m) =>
FromGeneric1 f a -> Code m (FromGeneric1 f a)
forall t.
(forall (m :: * -> *). Quote m => t -> m Exp)
-> (forall (m :: * -> *). Quote m => t -> Code m t) -> Lift t
forall (m :: * -> *). Quote m => FromGeneric1 f a -> m Exp
forall (m :: * -> *).
Quote m =>
FromGeneric1 f a -> Code m (FromGeneric1 f a)
$clift :: forall k (f :: k -> *) (a :: k) (m :: * -> *).
(Lift (f a), Quote m) =>
FromGeneric1 f a -> m Exp
lift :: forall (m :: * -> *). Quote m => FromGeneric1 f a -> m Exp
$cliftTyped :: forall k (f :: k -> *) (a :: k) (m :: * -> *).
(Lift (f a), Quote m) =>
FromGeneric1 f a -> Code m (FromGeneric1 f a)
liftTyped :: forall (m :: * -> *).
Quote m =>
FromGeneric1 f a -> Code m (FromGeneric1 f a)
Lift
#endif
)
deriving instance Foldable f => Foldable (FromGeneric1 f)
deriving instance Functor f => Functor (FromGeneric1 f)
deriving instance Traversable f => Traversable (FromGeneric1 f)
deriving instance Typeable FromGeneric1
deriving instance ( Data (f a), Typeable f, Typeable a
) => Data (FromGeneric1 f (a :: *))
instance (Generic1 f, GTextShowB (Rep1 f a)) => TextShow (FromGeneric1 f a) where
showbPrec :: Int -> FromGeneric1 f a -> Builder
showbPrec Int
p = Int -> Rep1 f a -> Builder
forall a. GTextShowB a => Int -> a -> Builder
gShowbPrec Int
p (Rep1 f a -> Builder)
-> (FromGeneric1 f a -> Rep1 f a) -> FromGeneric1 f a -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. f a -> Rep1 f a
forall (a :: k). f a -> Rep1 f a
forall k (f :: k -> *) (a :: k). Generic1 f => f a -> Rep1 f a
from1 (f a -> Rep1 f a)
-> (FromGeneric1 f a -> f a) -> FromGeneric1 f a -> Rep1 f a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FromGeneric1 f a -> f a
forall {k} (f :: k -> *) (a :: k). FromGeneric1 f a -> f a
fromGeneric1
instance ( Generic1 f
#if __GLASGOW_HASKELL__ >= 806 && __GLASGOW_HASKELL__ < 902
, g ~ Rep1 f, GTextShowB1 g
#else
, GTextShowB1 (Rep1 f)
#endif
) => TextShow1 (FromGeneric1 f) where
liftShowbPrec :: forall a.
(Int -> a -> Builder)
-> ([a] -> Builder) -> Int -> FromGeneric1 f a -> Builder
liftShowbPrec Int -> a -> Builder
sp [a] -> Builder
sl Int
p = (Int -> a -> Builder) -> ([a] -> Builder) -> Int -> f a -> Builder
forall (f :: * -> *) a.
(Generic1 f, GTextShowB1 (Rep1 f)) =>
(Int -> a -> Builder) -> ([a] -> Builder) -> Int -> f a -> Builder
genericLiftShowbPrec Int -> a -> Builder
sp [a] -> Builder
sl Int
p (f a -> Builder)
-> (FromGeneric1 f a -> f a) -> FromGeneric1 f a -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FromGeneric1 f a -> f a
forall {k} (f :: k -> *) (a :: k). FromGeneric1 f a -> f a
fromGeneric1
genericShowt :: (Generic a, GTextShowT (Rep a ())) => a -> TS.Text
genericShowt :: forall a. (Generic a, GTextShowT (Rep a ())) => a -> Text
genericShowt = Int -> a -> Text
forall a. (Generic a, GTextShowT (Rep a ())) => Int -> a -> Text
genericShowtPrec Int
0
genericShowtl :: (Generic a, GTextShowTL (Rep a ())) => a -> TL.Text
genericShowtl :: forall a. (Generic a, GTextShowTL (Rep a ())) => a -> Text
genericShowtl = Int -> a -> Text
forall a. (Generic a, GTextShowTL (Rep a ())) => Int -> a -> Text
genericShowtlPrec Int
0
genericShowtPrec :: (Generic a, GTextShowT (Rep a ())) => Int -> a -> TS.Text
genericShowtPrec :: forall a. (Generic a, GTextShowT (Rep a ())) => Int -> a -> Text
genericShowtPrec Int
p = Int -> Rep a () -> Text
forall a. GTextShowT a => Int -> a -> Text
gShowtPrec Int
p (Rep a () -> Text) -> (a -> Rep a ()) -> a -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Rep a ()
forall a. Generic a => a -> Rep a ()
fromRepUnit
genericShowtlPrec :: (Generic a, GTextShowTL (Rep a ())) => Int -> a -> TL.Text
genericShowtlPrec :: forall a. (Generic a, GTextShowTL (Rep a ())) => Int -> a -> Text
genericShowtlPrec Int
p = Int -> Rep a () -> Text
forall a. GTextShowTL a => Int -> a -> Text
gShowtlPrec Int
p (Rep a () -> Text) -> (a -> Rep a ()) -> a -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Rep a ()
forall a. Generic a => a -> Rep a ()
fromRepUnit
genericShowtList :: (Generic a, GTextShowT (Rep a ())) => [a] -> TS.Text
genericShowtList :: forall a. (Generic a, GTextShowT (Rep a ())) => [a] -> Text
genericShowtList = (a -> Text) -> [a] -> Text
forall a. (a -> Text) -> [a] -> Text
showtListWith a -> Text
forall a. (Generic a, GTextShowT (Rep a ())) => a -> Text
genericShowt
genericShowtlList :: (Generic a, GTextShowTL (Rep a ())) => [a] -> TL.Text
genericShowtlList :: forall a. (Generic a, GTextShowTL (Rep a ())) => [a] -> Text
genericShowtlList = (a -> Text) -> [a] -> Text
forall a. (a -> Text) -> [a] -> Text
showtlListWith a -> Text
forall a. (Generic a, GTextShowTL (Rep a ())) => a -> Text
genericShowtl
genericShowb :: (Generic a, GTextShowB (Rep a ())) => a -> Builder
genericShowb :: forall a. (Generic a, GTextShowB (Rep a ())) => a -> Builder
genericShowb = Int -> a -> Builder
forall a. (Generic a, GTextShowB (Rep a ())) => Int -> a -> Builder
genericShowbPrec Int
0
genericShowbPrec :: (Generic a, GTextShowB (Rep a ())) => Int -> a -> Builder
genericShowbPrec :: forall a. (Generic a, GTextShowB (Rep a ())) => Int -> a -> Builder
genericShowbPrec Int
p = Int -> Rep a () -> Builder
forall a. GTextShowB a => Int -> a -> Builder
gShowbPrec Int
p (Rep a () -> Builder) -> (a -> Rep a ()) -> a -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Rep a ()
forall a. Generic a => a -> Rep a ()
fromRepUnit
genericShowbList :: (Generic a, GTextShowB (Rep a ())) => [a] -> Builder
genericShowbList :: forall a. (Generic a, GTextShowB (Rep a ())) => [a] -> Builder
genericShowbList = (a -> Builder) -> [a] -> Builder
forall a. (a -> Builder) -> [a] -> Builder
showbListWith a -> Builder
forall a. (Generic a, GTextShowB (Rep a ())) => a -> Builder
genericShowb
genericPrintT :: (Generic a, GTextShowT (Rep a ())) => a -> IO ()
genericPrintT :: forall a. (Generic a, GTextShowT (Rep a ())) => a -> IO ()
genericPrintT = Text -> IO ()
TS.putStrLn (Text -> IO ()) -> (a -> Text) -> a -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Text
forall a. (Generic a, GTextShowT (Rep a ())) => a -> Text
genericShowt
genericPrintTL :: (Generic a, GTextShowTL (Rep a ())) => a -> IO ()
genericPrintTL :: forall a. (Generic a, GTextShowTL (Rep a ())) => a -> IO ()
genericPrintTL = Text -> IO ()
TL.putStrLn (Text -> IO ()) -> (a -> Text) -> a -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Text
forall a. (Generic a, GTextShowTL (Rep a ())) => a -> Text
genericShowtl
genericHPrintT :: (Generic a, GTextShowT (Rep a ())) => Handle -> a -> IO ()
genericHPrintT :: forall a.
(Generic a, GTextShowT (Rep a ())) =>
Handle -> a -> IO ()
genericHPrintT Handle
h = Handle -> Text -> IO ()
TS.hPutStrLn Handle
h (Text -> IO ()) -> (a -> Text) -> a -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Text
forall a. (Generic a, GTextShowT (Rep a ())) => a -> Text
genericShowt
genericHPrintTL :: (Generic a, GTextShowTL (Rep a ())) => Handle -> a -> IO ()
genericHPrintTL :: forall a.
(Generic a, GTextShowTL (Rep a ())) =>
Handle -> a -> IO ()
genericHPrintTL Handle
h = Handle -> Text -> IO ()
TL.hPutStrLn Handle
h (Text -> IO ()) -> (a -> Text) -> a -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Text
forall a. (Generic a, GTextShowTL (Rep a ())) => a -> Text
genericShowtl
genericLiftShowbPrec :: (Generic1 f, GTextShowB1 (Rep1 f))
=> (Int -> a -> Builder) -> ([a] -> Builder)
-> Int -> f a -> Builder
genericLiftShowbPrec :: forall (f :: * -> *) a.
(Generic1 f, GTextShowB1 (Rep1 f)) =>
(Int -> a -> Builder) -> ([a] -> Builder) -> Int -> f a -> Builder
genericLiftShowbPrec Int -> a -> Builder
sp [a] -> Builder
sl Int
p = (Int -> a -> Builder)
-> ([a] -> Builder) -> Int -> Rep1 f a -> Builder
forall a.
(Int -> a -> Builder)
-> ([a] -> Builder) -> Int -> Rep1 f a -> Builder
forall (f :: * -> *) a.
GTextShowB1 f =>
(Int -> a -> Builder) -> ([a] -> Builder) -> Int -> f a -> Builder
gLiftShowbPrec Int -> a -> Builder
sp [a] -> Builder
sl Int
p (Rep1 f a -> Builder) -> (f a -> Rep1 f a) -> f a -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. f a -> Rep1 f a
forall a. f a -> Rep1 f a
forall k (f :: k -> *) (a :: k). Generic1 f => f a -> Rep1 f a
from1
genericShowbPrec1 :: ( Generic a, Generic1 f
, GTextShowB (Rep a ())
, GTextShowB1 (Rep1 f)
)
=> Int -> f a -> Builder
genericShowbPrec1 :: forall a (f :: * -> *).
(Generic a, Generic1 f, GTextShowB (Rep a ()),
GTextShowB1 (Rep1 f)) =>
Int -> f a -> Builder
genericShowbPrec1 = (Int -> a -> Builder) -> ([a] -> Builder) -> Int -> f a -> Builder
forall (f :: * -> *) a.
(Generic1 f, GTextShowB1 (Rep1 f)) =>
(Int -> a -> Builder) -> ([a] -> Builder) -> Int -> f a -> Builder
genericLiftShowbPrec Int -> a -> Builder
forall a. (Generic a, GTextShowB (Rep a ())) => Int -> a -> Builder
genericShowbPrec [a] -> Builder
forall a. (Generic a, GTextShowB (Rep a ())) => [a] -> Builder
genericShowbList
fromRepUnit :: Generic a => a -> Rep a ()
fromRepUnit :: forall a. Generic a => a -> Rep a ()
fromRepUnit = a -> Rep a ()
forall x. a -> Rep a x
forall a x. Generic a => a -> Rep a x
from
data ConType = Rec | Tup | Pref | Inf String
deriving ( Typeable ConType
Typeable ConType =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ConType -> c ConType)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ConType)
-> (ConType -> Constr)
-> (ConType -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ConType))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ConType))
-> ((forall b. Data b => b -> b) -> ConType -> ConType)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ConType -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ConType -> r)
-> (forall u. (forall d. Data d => d -> u) -> ConType -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> ConType -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ConType -> m ConType)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ConType -> m ConType)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ConType -> m ConType)
-> Data ConType
ConType -> Constr
ConType -> DataType
(forall b. Data b => b -> b) -> ConType -> ConType
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) -> ConType -> u
forall u. (forall d. Data d => d -> u) -> ConType -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ConType -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ConType -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ConType -> m ConType
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ConType -> m ConType
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ConType
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ConType -> c ConType
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ConType)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ConType)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ConType -> c ConType
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ConType -> c ConType
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ConType
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ConType
$ctoConstr :: ConType -> Constr
toConstr :: ConType -> Constr
$cdataTypeOf :: ConType -> DataType
dataTypeOf :: ConType -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ConType)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ConType)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ConType)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ConType)
$cgmapT :: (forall b. Data b => b -> b) -> ConType -> ConType
gmapT :: (forall b. Data b => b -> b) -> ConType -> ConType
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ConType -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ConType -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ConType -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ConType -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> ConType -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> ConType -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> ConType -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> ConType -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ConType -> m ConType
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ConType -> m ConType
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ConType -> m ConType
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ConType -> m ConType
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ConType -> m ConType
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ConType -> m ConType
Data
, ConType -> ConType -> Bool
(ConType -> ConType -> Bool)
-> (ConType -> ConType -> Bool) -> Eq ConType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ConType -> ConType -> Bool
== :: ConType -> ConType -> Bool
$c/= :: ConType -> ConType -> Bool
/= :: ConType -> ConType -> Bool
Eq
, (forall x. ConType -> Rep ConType x)
-> (forall x. Rep ConType x -> ConType) -> Generic ConType
forall x. Rep ConType x -> ConType
forall x. ConType -> Rep ConType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ConType -> Rep ConType x
from :: forall x. ConType -> Rep ConType x
$cto :: forall x. Rep ConType x -> ConType
to :: forall x. Rep ConType x -> ConType
Generic
, Eq ConType
Eq ConType =>
(ConType -> ConType -> Ordering)
-> (ConType -> ConType -> Bool)
-> (ConType -> ConType -> Bool)
-> (ConType -> ConType -> Bool)
-> (ConType -> ConType -> Bool)
-> (ConType -> ConType -> ConType)
-> (ConType -> ConType -> ConType)
-> Ord ConType
ConType -> ConType -> Bool
ConType -> ConType -> Ordering
ConType -> ConType -> ConType
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
$ccompare :: ConType -> ConType -> Ordering
compare :: ConType -> ConType -> Ordering
$c< :: ConType -> ConType -> Bool
< :: ConType -> ConType -> Bool
$c<= :: ConType -> ConType -> Bool
<= :: ConType -> ConType -> Bool
$c> :: ConType -> ConType -> Bool
> :: ConType -> ConType -> Bool
$c>= :: ConType -> ConType -> Bool
>= :: ConType -> ConType -> Bool
$cmax :: ConType -> ConType -> ConType
max :: ConType -> ConType -> ConType
$cmin :: ConType -> ConType -> ConType
min :: ConType -> ConType -> ConType
Ord
, ReadPrec [ConType]
ReadPrec ConType
Int -> ReadS ConType
ReadS [ConType]
(Int -> ReadS ConType)
-> ReadS [ConType]
-> ReadPrec ConType
-> ReadPrec [ConType]
-> Read ConType
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ConType
readsPrec :: Int -> ReadS ConType
$creadList :: ReadS [ConType]
readList :: ReadS [ConType]
$creadPrec :: ReadPrec ConType
readPrec :: ReadPrec ConType
$creadListPrec :: ReadPrec [ConType]
readListPrec :: ReadPrec [ConType]
Read
, Int -> ConType -> ShowS
[ConType] -> ShowS
ConType -> String
(Int -> ConType -> ShowS)
-> (ConType -> String) -> ([ConType] -> ShowS) -> Show ConType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ConType -> ShowS
showsPrec :: Int -> ConType -> ShowS
$cshow :: ConType -> String
show :: ConType -> String
$cshowList :: [ConType] -> ShowS
showList :: [ConType] -> ShowS
Show
, Typeable
#if __GLASGOW_HASKELL__ >= 800
, (forall (m :: * -> *). Quote m => ConType -> m Exp)
-> (forall (m :: * -> *). Quote m => ConType -> Code m ConType)
-> Lift ConType
forall t.
(forall (m :: * -> *). Quote m => t -> m Exp)
-> (forall (m :: * -> *). Quote m => t -> Code m t) -> Lift t
forall (m :: * -> *). Quote m => ConType -> m Exp
forall (m :: * -> *). Quote m => ConType -> Code m ConType
$clift :: forall (m :: * -> *). Quote m => ConType -> m Exp
lift :: forall (m :: * -> *). Quote m => ConType -> m Exp
$cliftTyped :: forall (m :: * -> *). Quote m => ConType -> Code m ConType
liftTyped :: forall (m :: * -> *). Quote m => ConType -> Code m ConType
Lift
#endif
)
hashPrec :: Int -> Int
#if __GLASGOW_HASKELL__ >= 711
hashPrec :: Int -> Int
hashPrec = Int -> Int -> Int
forall a b. a -> b -> a
const Int
0
#else
hashPrec = id
#endif
#if __GLASGOW_HASKELL__ >= 711
#define HASH_FUNS(text_type,one_hash,two_hash,from_char,from_string) \
one_hash, two_hash :: text_type; \
one_hash = from_char '#'; \
two_hash = from_string "##";
#else
#define HASH_FUNS(text_type,one_hash,two_hash,from_char,from_string) \
one_hash, two_hash :: text_type; \
one_hash = mempty; \
two_hash = mempty;
#endif
#if __GLASGOW_HASKELL__ >= 902
#define INLINE_GE_902(f) {-# INLINE f #-};
#else
#define INLINE_GE_902(f)
#endif
#if __GLASGOW_HASKELL__ >= 806
#define QUANTIFIED_SUPERCLASS(class_name,f) (forall a. TextShow a => class_name (f a)) =>
#else
#define QUANTIFIED_SUPERCLASS(class_name,f)
#endif
#define GTEXT_SHOW(text_type,show_funs,one_hash,two_hash,gtext_show,gtext_show1,gshow_prec,glift_show_prec,gtext_show_con,gtext_show_con1,gshow_prec_con,glift_show_prec_con,show_prec,lift_show_prec,show_space,show_paren,show_list,show_list_with,from_char,from_string,c1_show_prec,s1_show_prec,product_show_prec,u_char_show_prec,u_double_show_prec,u_float_show_prec,u_int_show_prec,u_word_show_prec) \
{- | Class of generic representation types that can be converted to a \
'text_type'. \
\
/Since: 3.10/ \
-}; \
class gtext_show a where { \
; gshow_prec :: Int -> a -> text_type \
}; \
deriving instance Typeable gtext_show; \
\
instance gtext_show (f p) => gtext_show (D1 d f p) where { \
; gshow_prec p (M1 x) = gshow_prec p x \
}; \
\
instance gtext_show (V1 p) where { \
; gshow_prec _ x = case x of {} \
}; \
\
instance (gtext_show (f p), gtext_show (g p)) \
=> gtext_show ((f :+: g) p) where { \
; gshow_prec p (L1 x) = gshow_prec p x \
; gshow_prec p (R1 x) = gshow_prec p x \
}; \
\
instance (Constructor c, gtext_show_con (f p), IsNullary f) \
=> gtext_show (C1 c f p) where { \
gshow_prec = c1_show_prec gshow_prec_con \
}; \
\
{- | Class of generic representation types for which the 'ConType' has been \
determined. \
\
/Since: 3.10/ \
-}; \
class gtext_show_con a where { \
; gshow_prec_con :: ConType -> Int -> a -> text_type \
}; \
deriving instance Typeable gtext_show_con; \
\
instance gtext_show_con (U1 p) where { \
; gshow_prec_con _ _ U1 = mempty \
}; \
\
instance TextShow p => gtext_show_con (Par1 p) where { \
; gshow_prec_con _ p (Par1 x) = show_prec p x \
}; \
\
instance TextShow c => gtext_show_con (K1 i c p) where { \
; gshow_prec_con _ p (K1 x) = show_prec p x \
}; \
\
instance (TextShow1 f, TextShow p) => gtext_show_con (Rec1 f p) where { \
; gshow_prec_con _ p (Rec1 x) = lift_show_prec show_prec show_list p x \
}; \
\
instance (Selector s, gtext_show_con (f p)) => gtext_show_con (S1 s f p) where { \
; gshow_prec_con t = s1_show_prec $ gshow_prec_con t \
}; \
\
instance (gtext_show_con (f p), gtext_show_con (g p)) \
=> gtext_show_con ((f :*: g) p) where { \
; gshow_prec_con t = product_show_prec (gshow_prec_con t) (gshow_prec_con t) t \
}; \
\
instance (TextShow1 f, gtext_show_con (g p)) => gtext_show_con ((f :.: g) p) where { \
; gshow_prec_con t p (Comp1 x) = \
let gspc = gshow_prec_con t \
in lift_show_prec gspc (show_list_with (gspc 0)) p x \
}; \
\
instance gtext_show_con (UChar p) where { \
; gshow_prec_con _ = u_char_show_prec show_prec \
}; \
\
instance gtext_show_con (UDouble p) where { \
; gshow_prec_con _ = u_double_show_prec show_prec \
}; \
\
instance gtext_show_con (UFloat p) where { \
; gshow_prec_con _ = u_float_show_prec show_prec \
}; \
\
instance gtext_show_con (UInt p) where { \
; gshow_prec_con _ = u_int_show_prec show_prec \
}; \
\
instance gtext_show_con (UWord p) where { \
; gshow_prec_con _ = u_word_show_prec show_prec \
}; \
\
{- | Class of generic representation types for unary type constructors that can \
be converted to a 'text_type'. \
\
/Since: 3.10/ \
-}; \
class QUANTIFIED_SUPERCLASS(gtext_show,f) \
gtext_show1 f where { \
; glift_show_prec :: (Int -> a -> text_type) -> ([a] -> text_type) \
-> Int -> f a -> text_type \
}; \
deriving instance Typeable gtext_show1; \
\
instance gtext_show1 f => gtext_show1 (D1 d f) where { \
; glift_show_prec sp sl p (M1 x) = glift_show_prec sp sl p x \
}; \
\
instance gtext_show1 V1 where { \
; glift_show_prec _ _ _ x = case x of {} \
}; \
\
instance (gtext_show1 f, gtext_show1 g) => gtext_show1 (f :+: g) where { \
; glift_show_prec sp sl p (L1 x) = glift_show_prec sp sl p x \
; glift_show_prec sp sl p (R1 x) = glift_show_prec sp sl p x \
}; \
\
instance (Constructor c, gtext_show_con1 f, IsNullary f) \
=> gtext_show1 (C1 c f) where { \
; glift_show_prec sp sl = c1_show_prec $ glift_show_prec_con sp sl \
}; \
\
{- | Class of generic representation types for unary type constructors for which \
the 'ConType' has been determined. \
\
/Since: 3.10/ \
-}; \
class QUANTIFIED_SUPERCLASS(gtext_show_con,f) \
gtext_show_con1 f where { \
; glift_show_prec_con :: (Int -> a -> text_type) -> ([a] -> text_type) \
-> ConType -> Int -> f a -> text_type \
}; \
deriving instance Typeable gtext_show_con1; \
\
instance gtext_show_con1 U1 where { \
; glift_show_prec_con _ _ _ _ U1 = mempty \
}; \
\
instance gtext_show_con1 Par1 where { \
; glift_show_prec_con sp _ _ p (Par1 x) = sp p x \
}; \
\
instance TextShow c => gtext_show_con1 (K1 i c) where { \
; glift_show_prec_con _ _ _ p (K1 x) = show_prec p x \
}; \
\
instance TextShow1 f => gtext_show_con1 (Rec1 f) where { \
; glift_show_prec_con sp sl _ p (Rec1 x) = lift_show_prec sp sl p x \
}; \
\
instance (Selector s, gtext_show_con1 f) => gtext_show_con1 (S1 s f) where { \
; glift_show_prec_con sp sl t = s1_show_prec $ glift_show_prec_con sp sl t \
}; \
\
instance (gtext_show_con1 f, gtext_show_con1 g) \
=> gtext_show_con1 (f :*: g) where { \
; glift_show_prec_con sp sl t = \
product_show_prec (glift_show_prec_con sp sl t) (glift_show_prec_con sp sl t) t \
}; \
\
instance (TextShow1 f, gtext_show_con1 g) => gtext_show_con1 (f :.: g) where { \
; glift_show_prec_con sp sl t p (Comp1 x) = \
let gspc = glift_show_prec_con sp sl t \
in lift_show_prec gspc (show_list_with (gspc 0)) p x \
}; \
\
instance gtext_show_con1 UChar where { \
; glift_show_prec_con _ _ _ = u_char_show_prec show_prec \
}; \
\
instance gtext_show_con1 UDouble where { \
; glift_show_prec_con _ _ _ = u_double_show_prec show_prec \
}; \
\
instance gtext_show_con1 UFloat where { \
; glift_show_prec_con _ _ _ = u_float_show_prec show_prec \
}; \
\
instance gtext_show_con1 UInt where { \
; glift_show_prec_con _ _ _ = u_int_show_prec show_prec \
}; \
\
instance gtext_show_con1 UWord where { \
; glift_show_prec_con _ _ _ = u_word_show_prec show_prec \
}; \
\
c1_show_prec :: forall c f p. \
(Constructor c, IsNullary f) \
=> (ConType -> Int -> f p -> text_type) \
-> Int -> C1 c f p -> text_type; \
c1_show_prec sp p c@(M1 x) = case fixity of { \
; Prefix -> show_paren ( p > appPrec \
&& not (isNullary x || conIsTuple c) \
) $ \
(if conIsTuple c \
then mempty \
else let cn = conName c \
in show_paren (isInfixDataCon cn) $ from_string cn) \
<> (if isNullary x || conIsTuple c \
then mempty \
else from_char ' ') \
<> showBraces t (sp t appPrec1 x) \
; Infix _ m -> show_paren (p > m) $ sp t (m+1) x \
} where { \
; fixity :: Fixity \
; fixity = conFixity c \
\
; t :: ConType \
; t = if conIsRecord c \
then Rec \
else case conIsTuple c of { \
; True -> Tup \
; False -> case fixity of { \
; Prefix -> Pref \
; Infix _ _ -> Inf $ conName c \
}; \
}; \
\
; showBraces :: ConType -> text_type -> text_type \
; showBraces Rec b = from_char '{' <> b <> from_char '}' \
; showBraces Tup b = from_char '(' <> b <> from_char ')' \
; showBraces Pref b = b \
; showBraces (Inf _) b = b \
\
; conIsTuple :: C1 c f p -> Bool \
; conIsTuple = isTupleString . conName \
}; \
INLINE_GE_902(c1_show_prec) \
\
s1_show_prec :: Selector s \
=> (Int -> f p -> text_type) \
-> Int -> S1 s f p -> text_type; \
s1_show_prec sp p sel@(M1 x) \
| selName sel == "" = sp p x \
| otherwise = infixRec \
<> " = " \
<> sp 0 x \
where { \
; infixRec :: text_type \
; infixRec | isSymVar selectorName \
= from_char '(' <> from_string selectorName <> from_char ')' \
| otherwise \
= from_string selectorName \
\
; selectorName :: String \
; selectorName = selName sel \
}; \
INLINE_GE_902(s1_show_prec) \
\
product_show_prec :: (Int -> f p -> text_type) -> (Int -> g p -> text_type) \
-> ConType -> Int -> (f :*: g) p -> text_type; \
product_show_prec spf spg t p (a :*: b) = \
case t of { \
; Rec -> \
spf 0 a \
<> ", " \
<> spg 0 b \
; Inf o -> \
spf p a \
<> show_space \
<> infixOp o \
<> show_space \
<> spg p b \
; Tup -> \
spf 0 a \
<> from_char ',' \
<> spg 0 b \
; Pref -> \
spf p a \
<> show_space \
<> spg p b \
} where { \
; infixOp :: String -> text_type \
; infixOp o = if isInfixDataCon o \
then from_string o \
else from_char '`' <> from_string o <> from_char '`' \
}; \
INLINE_GE_902(product_show_prec) \
\
u_char_show_prec :: (Int -> Char -> text_type) -> Int -> UChar p -> text_type; \
u_char_show_prec sp p (UChar c) = sp (hashPrec p) (C# c) <> one_hash; \
INLINE_GE_902(u_char_show_prec) \
\
u_double_show_prec :: (Int -> Double -> text_type) -> Int -> UDouble p -> text_type; \
u_double_show_prec sp p (UDouble d) = sp (hashPrec p) (D# d) <> two_hash; \
INLINE_GE_902(u_double_show_prec) \
\
u_float_show_prec :: (Int -> Float -> text_type) -> Int -> UFloat p -> text_type; \
u_float_show_prec sp p (UFloat f) = sp (hashPrec p) (F# f) <> one_hash; \
INLINE_GE_902(u_float_show_prec) \
\
u_int_show_prec :: (Int -> Int -> text_type) -> Int -> UInt p -> text_type; \
u_int_show_prec sp p (UInt i) = sp (hashPrec p) (I# i) <> one_hash; \
INLINE_GE_902(u_int_show_prec) \
\
u_word_show_prec :: (Int -> Word -> text_type) -> Int -> UWord p -> text_type; \
u_word_show_prec sp p (UWord w) = sp (hashPrec p) (W# w) <> two_hash; \
INLINE_GE_902(u_word_show_prec) \
\
HASH_FUNS(text_type,one_hash,two_hash,from_char,from_string);
GTEXT_SHOW(Builder,ShowFunsB,oneHashB,twoHashB,GTextShowB,GTextShowB1,gShowbPrec,gLiftShowbPrec,GTextShowConB,GTextShowConB1,gShowbPrecCon,gLiftShowbPrecCon,showbPrec,liftShowbPrec,showbSpace,showbParen,showbList,showbListWith,TB.singleton,TB.fromString,c1ShowbPrec,s1ShowbPrec,productShowbPrec,uCharShowbPrec,uDoubleShowbPrec,uFloatShowbPrec,uIntShowbPrec,uWordShowbPrec)
GTEXT_SHOW(TS.Text,ShowFunsT,oneHashT,twoHashT,GTextShowT,GTextShowT1,gShowtPrec,gLiftShowtPrec,GTextShowConT,GTextShowConT1,gShowtPrecCon,gLiftShowtPrecCon,showtPrec,liftShowtPrec,showtSpace,showtParen,showtList,showtListWith,TS.singleton,TS.pack,c1ShowtPrec,s1ShowtPrec,productShowtPrec,uCharShowtPrec,uDoubleShowtPrec,uFloatShowtPrec,uIntShowtPrec,uWordShowtPrec)
GTEXT_SHOW(TL.Text,ShowFunsTL,oneHashTL,twoHashTL,GTextShowTL,GTextShowTL1,gShowtlPrec,gLiftShowtlPrec,GTextShowConTL,GTextShowConTL1,gShowtlPrecCon,gLiftShowtlPrecCon,showtlPrec,liftShowtlPrec,showtlSpace,showtlParen,showtlList,showtlListWith,TL.singleton,TL.pack,c1ShowtlPrec,s1ShowtlPrec,productShowtlPrec,uCharShowtlPrec,uDoubleShowtlPrec,uFloatShowtlPrec,uIntShowtlPrec,uWordShowtlPrec)
class IsNullary f where
isNullary :: f a -> Bool
instance IsNullary U1 where
isNullary :: forall (a :: k). U1 a -> Bool
isNullary U1 a
_ = Bool
True
instance IsNullary Par1 where
isNullary :: forall a. Par1 a -> Bool
isNullary Par1 a
_ = Bool
False
instance IsNullary (K1 i c) where
isNullary :: forall (a :: k). K1 i c a -> Bool
isNullary K1 i c a
_ = Bool
False
instance IsNullary f => IsNullary (S1 s f) where
isNullary :: forall (a :: k). S1 s f a -> Bool
isNullary (M1 f a
x) = f a -> Bool
forall (a :: k). f a -> Bool
forall {k} (f :: k -> *) (a :: k). IsNullary f => f a -> Bool
isNullary f a
x
instance IsNullary (Rec1 f) where
isNullary :: forall (a :: k). Rec1 f a -> Bool
isNullary Rec1 f a
_ = Bool
False
instance IsNullary (f :*: g) where
isNullary :: forall (a :: k). (:*:) f g a -> Bool
isNullary (:*:) f g a
_ = Bool
False
instance IsNullary (f :.: g) where
isNullary :: forall (a :: k). (:.:) f g a -> Bool
isNullary (:.:) f g a
_ = Bool
False
instance IsNullary UChar where
isNullary :: forall (a :: k). UChar a -> Bool
isNullary UChar a
_ = Bool
False
instance IsNullary UDouble where
isNullary :: forall (a :: k). UDouble a -> Bool
isNullary UDouble a
_ = Bool
False
instance IsNullary UFloat where
isNullary :: forall (a :: k). UFloat a -> Bool
isNullary UFloat a
_ = Bool
False
instance IsNullary UInt where
isNullary :: forall (a :: k). UInt a -> Bool
isNullary UInt a
_ = Bool
False
instance IsNullary UWord where
isNullary :: forall (a :: k). UWord a -> Bool
isNullary UWord a
_ = Bool
False
$(deriveTextShow ''ConType)
#if __GLASGOW_HASKELL__ < 800
$(deriveLift ''ConType)
$(deriveLift ''FromGeneric)
instance Lift (f a) => Lift (FromGeneric1 f a) where
lift = $(makeLift ''FromGeneric1)
#endif
#if !defined(__LANGUAGE_DERIVE_GENERIC1__)
$(Generics.deriveMeta ''FromGeneric1)
$(Generics.deriveRepresentable1 ''FromGeneric1)
#endif