{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE Trustworthy #-}

-----------------------------------------------------------------------------
-- |
-- Module      :  Data.Functor.Const
-- Copyright   :  Conor McBride and Ross Paterson 2005
-- License     :  BSD-style (see the LICENSE file in the distribution)
--
-- Maintainer  :  libraries@haskell.org
-- Stability   :  experimental
-- Portability :  portable

-- The 'Const' functor.
--
-- @since 4.9.0.0

module Data.Functor.Const (Const(..)) where

import Data.Bits (Bits, FiniteBits)
import Data.Foldable (Foldable(foldMap))
import Foreign.Storable (Storable)

import GHC.Ix (Ix)
import GHC.Base
import GHC.Enum (Bounded, Enum)
import GHC.Float (Floating, RealFloat)
import GHC.Generics (Generic, Generic1)
import GHC.Num (Num)
import GHC.Real (Fractional, Integral, Real, RealFrac)
import GHC.Read (Read(readsPrec), readParen, lex)
import GHC.Show (Show(showsPrec), showParen, showString)

-- | The 'Const' functor.
newtype Const a b = Const { Const a b -> a
getConst :: a }
    deriving ( Bits       -- ^ @since 4.9.0.0
             , Bounded    -- ^ @since 4.9.0.0
             , Enum       -- ^ @since 4.9.0.0
             , Eq         -- ^ @since 4.9.0.0
             , FiniteBits -- ^ @since 4.9.0.0
             , Floating   -- ^ @since 4.9.0.0
             , Fractional -- ^ @since 4.9.0.0
             , Generic    -- ^ @since 4.9.0.0
             , Generic1   -- ^ @since 4.9.0.0
             , Integral   -- ^ @since 4.9.0.0
             , Ix         -- ^ @since 4.9.0.0
             , Semigroup  -- ^ @since 4.9.0.0
             , Monoid     -- ^ @since 4.9.0.0
             , Num        -- ^ @since 4.9.0.0
             , Ord        -- ^ @since 4.9.0.0
             , Real       -- ^ @since 4.9.0.0
             , RealFrac   -- ^ @since 4.9.0.0
             , RealFloat  -- ^ @since 4.9.0.0
             , Storable   -- ^ @since 4.9.0.0
             )

-- | This instance would be equivalent to the derived instances of the
-- 'Const' newtype if the 'getConst' field were removed
--
-- @since 4.8.0.0
instance Read a => Read (Const a b) where
    readsPrec :: Int -> ReadS (Const a b)
readsPrec Int
d = Bool -> ReadS (Const a b) -> ReadS (Const a b)
forall a. Bool -> ReadS a -> ReadS a
readParen (Int
d Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
External instance of the constraint type Ord Int
> Int
10)
        (ReadS (Const a b) -> ReadS (Const a b))
-> ReadS (Const a b) -> ReadS (Const a b)
forall a b. (a -> b) -> a -> b
$ \String
r -> [(a -> Const a b
forall {k} a (b :: k). a -> Const a b
Const a
x,String
t) | (String
"Const", String
s) <- ReadS String
lex String
r, (a
x, String
t) <- Int -> ReadS a
forall a. Read a => Int -> ReadS a
Evidence bound by a type signature of the constraint type Read a
readsPrec Int
11 String
s]

-- | This instance would be equivalent to the derived instances of the
-- 'Const' newtype if the 'getConst' field were removed
--
-- @since 4.8.0.0
instance Show a => Show (Const a b) where
    showsPrec :: Int -> Const a b -> ShowS
showsPrec Int
d (Const a
x) = Bool -> ShowS -> ShowS
showParen (Int
d Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
External instance of the constraint type Ord Int
> Int
10) (ShowS -> ShowS) -> ShowS -> ShowS
forall a b. (a -> b) -> a -> b
$
                            String -> ShowS
showString String
"Const " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> a -> ShowS
forall a. Show a => Int -> a -> ShowS
Evidence bound by a type signature of the constraint type Show a
showsPrec Int
11 a
x

-- | @since 4.7.0.0
instance Foldable (Const m) where
    foldMap :: (a -> m) -> Const m a -> m
foldMap a -> m
_ Const m a
_ = m
forall a. Monoid a => a
Evidence bound by a type signature of the constraint type Monoid m
mempty

-- | @since 2.01
instance Functor (Const m) where
    fmap :: (a -> b) -> Const m a -> Const m b
fmap a -> b
_ (Const m
v) = m -> Const m b
forall {k} a (b :: k). a -> Const a b
Const m
v

-- | @since 2.0.1
instance Monoid m => Applicative (Const m) where
    pure :: a -> Const m a
pure a
_ = m -> Const m a
forall {k} a (b :: k). a -> Const a b
Const m
forall a. Monoid a => a
Evidence bound by a type signature of the constraint type Monoid m
mempty
    liftA2 :: (a -> b -> c) -> Const m a -> Const m b -> Const m c
liftA2 a -> b -> c
_ (Const m
x) (Const m
y) = m -> Const m c
forall {k} a (b :: k). a -> Const a b
Const (m
x m -> m -> m
forall a. Monoid a => a -> a -> a
Evidence bound by a type signature of the constraint type Monoid m
`mappend` m
y)
    <*> :: Const m (a -> b) -> Const m a -> Const m b
(<*>) = (m -> m -> m) -> Const m (a -> b) -> Const m a -> Const m b
coerce (m -> m -> m
forall a. Monoid a => a -> a -> a
Evidence bound by a type signature of the constraint type Monoid m
mappend :: m -> m -> m)
-- This is pretty much the same as
-- Const f <*> Const v = Const (f `mappend` v)
-- but guarantees that mappend for Const a b will have the same arity
-- as the one for a; it won't create a closure to raise the arity
-- to 2.