#if __GLASGOW_HASKELL__ >= 702
#else
#endif
#if __GLASGOW_HASKELL__ >= 708
#endif
module TextShow.FromStringTextShow (FromStringShow(..), FromTextShow(..)) where
import Data.Data (Data, Typeable)
#if __GLASGOW_HASKELL__ >= 702
import GHC.Generics (Generic)
# if __GLASGOW_HASKELL__ >= 706
import GHC.Generics (Generic1)
# endif
#else
import qualified Generics.Deriving.TH as Generics (deriveAll)
#endif
import Prelude ()
import Prelude.Compat
import Text.Read (Read(..), readListPrecDefault)
import TextShow.Classes (TextShow(..), TextShow1(..),
showbToShows, showsToShowb)
#include "inline.h"
newtype FromStringShow a = FromStringShow { fromStringShow :: a }
deriving ( Data
, Eq
, Foldable
, Functor
#if __GLASGOW_HASKELL__ >= 702
, Generic
# if __GLASGOW_HASKELL__ >= 706
, Generic1
# endif
#endif
, Ord
, Traversable
, Typeable
)
instance Read a => Read (FromStringShow a) where
readPrec = FromStringShow <$> readPrec
INLINE_INST_FUN(readPrec)
readListPrec = readListPrecDefault
INLINE_INST_FUN(readListPrec)
instance Show a => TextShow (FromStringShow a) where
showbPrec p = showsToShowb showsPrec p . fromStringShow
INLINE_INST_FUN(showbPrec)
instance Show a => Show (FromStringShow a) where
showsPrec p = showsPrec p . fromStringShow
INLINE_INST_FUN(showsPrec)
instance TextShow1 FromStringShow where
showbPrecWith sp p =
showsToShowb (showbToShows sp) p . fromStringShow
INLINE_INST_FUN(showbPrecWith)
newtype FromTextShow a = FromTextShow { fromTextShow :: a }
deriving ( Data
, Eq
, Foldable
, Functor
#if __GLASGOW_HASKELL__ >= 702
, Generic
# if __GLASGOW_HASKELL__ >= 706
, Generic1
# endif
#endif
, Ord
, TextShow
, Traversable
, Typeable
)
instance Read a => Read (FromTextShow a) where
readPrec = FromTextShow <$> readPrec
INLINE_INST_FUN(readPrec)
readListPrec = readListPrecDefault
INLINE_INST_FUN(readListPrec)
instance TextShow a => Show (FromTextShow a) where
showsPrec p = showbToShows showbPrec p . fromTextShow
INLINE_INST_FUN(showsPrec)
instance TextShow1 FromTextShow where
showbPrecWith sp p = sp p . fromTextShow
INLINE_INST_FUN(showbPrecWith)
#if __GLASGOW_HASKELL__ < 702
$(Generics.deriveAll ''FromStringShow)
$(Generics.deriveAll ''FromTextShow)
#endif