coerce-util-0.1.0.0: utils for Data.Coerce

Safe HaskellNone
LanguageHaskell2010

Data.Coerce.Util

Contents

Synopsis

Function coercion utils

(#.) :: Coercible b c => (b -> c) -> (a -> b) -> a -> c infixr 9 Source #

Coercive left-composition.

(.#) :: Coercible a b => (b -> c) -> (a -> b) -> a -> c infixr 9 Source #

Coercive right-composition.

Shorten coercion type signatures

type Binary a = a -> a -> a Source #

type CoerceBinary a b = Binary a -> Binary b Source #

type WrapBinary f a = Binary a -> WrappedBinary f a Source #

type WrappedBinary f a = Binary (f a) Source #

Newtype utils

showsNewtype :: Coercible b a => String -> String -> (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> b -> ShowS Source #

A definition for liftShowsPrec, suitable for newtypes.

Given a newtype declared as:

newtype T a = T { unT :: a }

The Show1 definition can be given as:

instance Show1 T where
  liftShowsPrec = showsNewtype T "unT"

readsNewtype :: Coercible a b => String -> String -> (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS b Source #

A definition for liftReadsPrec, suitable for newtypes.

Given a newtype declared as:

newtype T a = T { unT :: a }

The Read1 definition can be given as:

instance Read1 T where
  liftReadsPrec = readsNewtype T "unT"