base-orphans-0.6: Backwards-compatible orphan instances for base

Safe HaskellTrustworthy
LanguageHaskell2010

Data.Orphans

Contents

Description

Exports orphan instances that mimic instances available in later versions of base. To use them, simply import Data.Orphans ().

Orphan instances

Semigroup Event Source # 

Methods

(<>) :: Event -> Event -> Event #

sconcat :: NonEmpty Event -> Event #

stimes :: Integral b => b -> Event -> Event #

Semigroup Lifetime Source # 
Eq1 NonEmpty Source # 

Methods

liftEq :: (a -> b -> Bool) -> NonEmpty a -> NonEmpty b -> Bool #

Ord1 NonEmpty Source # 

Methods

liftCompare :: (a -> b -> Ordering) -> NonEmpty a -> NonEmpty b -> Ordering #

Read1 NonEmpty Source # 

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (NonEmpty a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [NonEmpty a] #

Show1 NonEmpty Source # 

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> NonEmpty a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [NonEmpty a] -> ShowS #

Semigroup a => Semigroup (IO a) Source # 

Methods

(<>) :: IO a -> IO a -> IO a #

sconcat :: NonEmpty (IO a) -> IO a #

stimes :: Integral b => b -> IO a -> IO a #

(Typeable * k2, Data a, Typeable k2 b) => Data (Const k2 a b) Source # 

Methods

gfoldl :: (forall d c. Data d => c (d -> c) -> d -> c c) -> (forall g. g -> c g) -> Const k2 a b -> c (Const k2 a b) #

gunfold :: (forall c r. Data c => c (c -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Const k2 a b) #

toConstr :: Const k2 a b -> Constr #

dataTypeOf :: Const k2 a b -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Const k2 a b)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Const k2 a b)) #

gmapT :: (forall c. Data c => c -> c) -> Const k2 a b -> Const k2 a b #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Const k2 a b -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Const k2 a b -> r #

gmapQ :: (forall d. Data d => d -> u) -> Const k2 a b -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Const k2 a b -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Const k2 a b -> m (Const k2 a b) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Const k2 a b -> m (Const k2 a b) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Const k2 a b -> m (Const k2 a b) #