{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE Safe #-}
-----------------------------------------------------------------------------
-- |
-- Module      :  Data.Functor.Sum
-- Copyright   :  (c) Ross Paterson 2014
-- License     :  BSD-style (see the file LICENSE)
--
-- Maintainer  :  libraries@haskell.org
-- Stability   :  experimental
-- Portability :  portable
--
-- Sums, lifted to functors.
--
-- @since 4.9.0.0
-----------------------------------------------------------------------------

module Data.Functor.Sum (
    Sum(..),
  ) where

import Control.Applicative ((<|>))
import Data.Data (Data)
import Data.Functor.Classes
import GHC.Generics (Generic, Generic1)
import Text.Read (Read(..), readListDefault, readListPrecDefault)

-- | Lifted sum of functors.
data Sum f g a = InL (f a) | InR (g a)
  deriving ( Data     -- ^ @since 4.9.0.0
           , Generic  -- ^ @since 4.9.0.0
           , Generic1 -- ^ @since 4.9.0.0
           )

-- | @since 4.9.0.0
instance (Eq1 f, Eq1 g) => Eq1 (Sum f g) where
    liftEq :: (a -> b -> Bool) -> Sum f g a -> Sum f g b -> Bool
liftEq eq :: a -> b -> Bool
eq (InL x1 :: f a
x1) (InL x2 :: f b
x2) = (a -> b -> Bool) -> f a -> f b -> Bool
forall (f :: * -> *) a b.
Eq1 f =>
(a -> b -> Bool) -> f a -> f b -> Bool
liftEq a -> b -> Bool
eq f a
x1 f b
x2
    liftEq _ (InL _) (InR _) = Bool
False
    liftEq _ (InR _) (InL _) = Bool
False
    liftEq eq :: a -> b -> Bool
eq (InR y1 :: g a
y1) (InR y2 :: g b
y2) = (a -> b -> Bool) -> g a -> g b -> Bool
forall (f :: * -> *) a b.
Eq1 f =>
(a -> b -> Bool) -> f a -> f b -> Bool
liftEq a -> b -> Bool
eq g a
y1 g b
y2

-- | @since 4.9.0.0
instance (Ord1 f, Ord1 g) => Ord1 (Sum f g) where
    liftCompare :: (a -> b -> Ordering) -> Sum f g a -> Sum f g b -> Ordering
liftCompare comp :: a -> b -> Ordering
comp (InL x1 :: f a
x1) (InL x2 :: f b
x2) = (a -> b -> Ordering) -> f a -> f b -> Ordering
forall (f :: * -> *) a b.
Ord1 f =>
(a -> b -> Ordering) -> f a -> f b -> Ordering
liftCompare a -> b -> Ordering
comp f a
x1 f b
x2
    liftCompare _ (InL _) (InR _) = Ordering
LT
    liftCompare _ (InR _) (InL _) = Ordering
GT
    liftCompare comp :: a -> b -> Ordering
comp (InR y1 :: g a
y1) (InR y2 :: g b
y2) = (a -> b -> Ordering) -> g a -> g b -> Ordering
forall (f :: * -> *) a b.
Ord1 f =>
(a -> b -> Ordering) -> f a -> f b -> Ordering
liftCompare a -> b -> Ordering
comp g a
y1 g b
y2

-- | @since 4.9.0.0
instance (Read1 f, Read1 g) => Read1 (Sum f g) where
    liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Sum f g a)
liftReadPrec rp :: ReadPrec a
rp rl :: ReadPrec [a]
rl = ReadPrec (Sum f g a) -> ReadPrec (Sum f g a)
forall a. ReadPrec a -> ReadPrec a
readData (ReadPrec (Sum f g a) -> ReadPrec (Sum f g a))
-> ReadPrec (Sum f g a) -> ReadPrec (Sum f g a)
forall a b. (a -> b) -> a -> b
$
        ReadPrec (f a)
-> String -> (f a -> Sum f g a) -> ReadPrec (Sum f g a)
forall a t. ReadPrec a -> String -> (a -> t) -> ReadPrec t
readUnaryWith (ReadPrec a -> ReadPrec [a] -> ReadPrec (f a)
forall (f :: * -> *) a.
Read1 f =>
ReadPrec a -> ReadPrec [a] -> ReadPrec (f a)
liftReadPrec ReadPrec a
rp ReadPrec [a]
rl) "InL" f a -> Sum f g a
forall k (f :: k -> *) (g :: k -> *) (a :: k). f a -> Sum f g a
InL ReadPrec (Sum f g a)
-> ReadPrec (Sum f g a) -> ReadPrec (Sum f g a)
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|>
        ReadPrec (g a)
-> String -> (g a -> Sum f g a) -> ReadPrec (Sum f g a)
forall a t. ReadPrec a -> String -> (a -> t) -> ReadPrec t
readUnaryWith (ReadPrec a -> ReadPrec [a] -> ReadPrec (g a)
forall (f :: * -> *) a.
Read1 f =>
ReadPrec a -> ReadPrec [a] -> ReadPrec (f a)
liftReadPrec ReadPrec a
rp ReadPrec [a]
rl) "InR" g a -> Sum f g a
forall k (f :: k -> *) (g :: k -> *) (a :: k). g a -> Sum f g a
InR

    liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Sum f g a]
liftReadListPrec = ReadPrec a -> ReadPrec [a] -> ReadPrec [Sum f g a]
forall (f :: * -> *) a.
Read1 f =>
ReadPrec a -> ReadPrec [a] -> ReadPrec [f a]
liftReadListPrecDefault
    liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Sum f g a]
liftReadList     = (Int -> ReadS a) -> ReadS [a] -> ReadS [Sum f g a]
forall (f :: * -> *) a.
Read1 f =>
(Int -> ReadS a) -> ReadS [a] -> ReadS [f a]
liftReadListDefault

-- | @since 4.9.0.0
instance (Show1 f, Show1 g) => Show1 (Sum f g) where
    liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Sum f g a -> ShowS
liftShowsPrec sp :: Int -> a -> ShowS
sp sl :: [a] -> ShowS
sl d :: Int
d (InL x :: f a
x) =
        (Int -> f a -> ShowS) -> String -> Int -> f a -> ShowS
forall a. (Int -> a -> ShowS) -> String -> Int -> a -> ShowS
showsUnaryWith ((Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> f a -> ShowS
forall (f :: * -> *) a.
Show1 f =>
(Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> f a -> ShowS
liftShowsPrec Int -> a -> ShowS
sp [a] -> ShowS
sl) "InL" Int
d f a
x
    liftShowsPrec sp :: Int -> a -> ShowS
sp sl :: [a] -> ShowS
sl d :: Int
d (InR y :: g a
y) =
        (Int -> g a -> ShowS) -> String -> Int -> g a -> ShowS
forall a. (Int -> a -> ShowS) -> String -> Int -> a -> ShowS
showsUnaryWith ((Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> g a -> ShowS
forall (f :: * -> *) a.
Show1 f =>
(Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> f a -> ShowS
liftShowsPrec Int -> a -> ShowS
sp [a] -> ShowS
sl) "InR" Int
d g a
y

-- | @since 4.9.0.0
instance (Eq1 f, Eq1 g, Eq a) => Eq (Sum f g a) where
    == :: Sum f g a -> Sum f g a -> Bool
(==) = Sum f g a -> Sum f g a -> Bool
forall (f :: * -> *) a. (Eq1 f, Eq a) => f a -> f a -> Bool
eq1
-- | @since 4.9.0.0
instance (Ord1 f, Ord1 g, Ord a) => Ord (Sum f g a) where
    compare :: Sum f g a -> Sum f g a -> Ordering
compare = Sum f g a -> Sum f g a -> Ordering
forall (f :: * -> *) a. (Ord1 f, Ord a) => f a -> f a -> Ordering
compare1
-- | @since 4.9.0.0
instance (Read1 f, Read1 g, Read a) => Read (Sum f g a) where
    readPrec :: ReadPrec (Sum f g a)
readPrec = ReadPrec (Sum f g a)
forall (f :: * -> *) a. (Read1 f, Read a) => ReadPrec (f a)
readPrec1

    readListPrec :: ReadPrec [Sum f g a]
readListPrec = ReadPrec [Sum f g a]
forall a. Read a => ReadPrec [a]
readListPrecDefault
    readList :: ReadS [Sum f g a]
readList     = ReadS [Sum f g a]
forall a. Read a => ReadS [a]
readListDefault
-- | @since 4.9.0.0
instance (Show1 f, Show1 g, Show a) => Show (Sum f g a) where
    showsPrec :: Int -> Sum f g a -> ShowS
showsPrec = Int -> Sum f g a -> ShowS
forall (f :: * -> *) a. (Show1 f, Show a) => Int -> f a -> ShowS
showsPrec1

-- | @since 4.9.0.0
instance (Functor f, Functor g) => Functor (Sum f g) where
    fmap :: (a -> b) -> Sum f g a -> Sum f g b
fmap f :: a -> b
f (InL x :: f a
x) = f b -> Sum f g b
forall k (f :: k -> *) (g :: k -> *) (a :: k). f a -> Sum f g a
InL ((a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
f f a
x)
    fmap f :: a -> b
f (InR y :: g a
y) = g b -> Sum f g b
forall k (f :: k -> *) (g :: k -> *) (a :: k). g a -> Sum f g a
InR ((a -> b) -> g a -> g b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
f g a
y)

-- | @since 4.9.0.0
instance (Foldable f, Foldable g) => Foldable (Sum f g) where
    foldMap :: (a -> m) -> Sum f g a -> m
foldMap f :: a -> m
f (InL x :: f a
x) = (a -> m) -> f a -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap a -> m
f f a
x
    foldMap f :: a -> m
f (InR y :: g a
y) = (a -> m) -> g a -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap a -> m
f g a
y

-- | @since 4.9.0.0
instance (Traversable f, Traversable g) => Traversable (Sum f g) where
    traverse :: (a -> f b) -> Sum f g a -> f (Sum f g b)
traverse f :: a -> f b
f (InL x :: f a
x) = f b -> Sum f g b
forall k (f :: k -> *) (g :: k -> *) (a :: k). f a -> Sum f g a
InL (f b -> Sum f g b) -> f (f b) -> f (Sum f g b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (a -> f b) -> f a -> f (f b)
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse a -> f b
f f a
x
    traverse f :: a -> f b
f (InR y :: g a
y) = g b -> Sum f g b
forall k (f :: k -> *) (g :: k -> *) (a :: k). g a -> Sum f g a
InR (g b -> Sum f g b) -> f (g b) -> f (Sum f g b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (a -> f b) -> g a -> f (g b)
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse a -> f b
f g a
y