#if __GLASGOW_HASKELL__ >= 702
#endif
#if __GLASGOW_HASKELL__ >= 706
#endif
#if __GLASGOW_HASKELL__ >= 710
#endif
module Data.Functor.Constant (
Constant(..),
) where
import Data.Functor.Classes
#if MIN_VERSION_base(4,12,0)
import Data.Functor.Contravariant
#endif
import Control.Applicative
import Data.Foldable
import Data.Monoid (Monoid(..))
import Data.Traversable (Traversable(traverse))
#if MIN_VERSION_base(4,8,0)
import Data.Bifunctor (Bifunctor(..))
#endif
#if MIN_VERSION_base(4,9,0)
import Data.Semigroup (Semigroup(..))
#endif
#if MIN_VERSION_base(4,10,0)
import Data.Bifoldable (Bifoldable(..))
import Data.Bitraversable (Bitraversable(..))
#endif
import Prelude hiding (null, length)
newtype Constant a b = Constant { getConstant :: a }
deriving (Eq, Ord)
instance (Read a) => Read (Constant a b) where
readsPrec = readsData $
readsUnaryWith readsPrec "Constant" Constant
instance (Show a) => Show (Constant a b) where
showsPrec d (Constant x) = showsUnaryWith showsPrec "Constant" d x
instance Eq2 Constant where
liftEq2 eq _ (Constant x) (Constant y) = eq x y
instance Ord2 Constant where
liftCompare2 comp _ (Constant x) (Constant y) = comp x y
instance Read2 Constant where
liftReadsPrec2 rp _ _ _ = readsData $
readsUnaryWith rp "Constant" Constant
instance Show2 Constant where
liftShowsPrec2 sp _ _ _ d (Constant x) = showsUnaryWith sp "Constant" d x
instance (Eq a) => Eq1 (Constant a) where
liftEq = liftEq2 (==)
instance (Ord a) => Ord1 (Constant a) where
liftCompare = liftCompare2 compare
instance (Read a) => Read1 (Constant a) where
liftReadsPrec = liftReadsPrec2 readsPrec readList
instance (Show a) => Show1 (Constant a) where
liftShowsPrec = liftShowsPrec2 showsPrec showList
instance Functor (Constant a) where
fmap _ (Constant x) = Constant x
instance Foldable (Constant a) where
foldMap _ (Constant _) = mempty
#if MIN_VERSION_base(4,8,0)
null (Constant _) = True
length (Constant _) = 0
#endif
instance Traversable (Constant a) where
traverse _ (Constant x) = pure (Constant x)
#if MIN_VERSION_base(4,9,0)
instance (Semigroup a) => Semigroup (Constant a b) where
Constant x <> Constant y = Constant (x <> y)
#endif
instance (Monoid a) => Applicative (Constant a) where
pure _ = Constant mempty
Constant x <*> Constant y = Constant (x `mappend` y)
instance (Monoid a) => Monoid (Constant a b) where
mempty = Constant mempty
#if !MIN_VERSION_base(4,11,0)
Constant x `mappend` Constant y = Constant (x `mappend` y)
#endif
#if MIN_VERSION_base(4,8,0)
instance Bifunctor Constant where
first f (Constant x) = Constant (f x)
second _ (Constant x) = Constant x
#endif
#if MIN_VERSION_base(4,10,0)
instance Bifoldable Constant where
bifoldMap f _ (Constant a) = f a
instance Bitraversable Constant where
bitraverse f _ (Constant a) = Constant <$> f a
#endif
#if MIN_VERSION_base(4,12,0)
instance Contravariant (Constant a) where
contramap _ (Constant a) = Constant a
#endif