{-# LANGUAGE Safe #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
----------------------------------------------------------------------------
-- |
-- Module      :  Algebra.PartialOrd.Instances
-- Copyright   :  (C) 2010-2015 Maximilian Bolingbroke, 2015 Oleg Grenrus
-- License     :  BSD-3-Clause (see the file LICENSE)
--
-- Maintainer  :  Oleg Grenrus <oleg.grenrus@iki.fi>
--
-- This module re-exports orphan instances from 'Data.Universe.Instances.Eq'
-- module, and @(PartialOrd v, Finite k) => PartialOrd (k -> v)@ instance.
----------------------------------------------------------------------------
module Algebra.PartialOrd.Instances () where

import Algebra.PartialOrd         (PartialOrd (..))
import Data.Monoid                (Endo (..))
import Data.Universe.Class        (Finite (..))
import Data.Universe.Instances.Eq ()

-- | @Eq (k -> v)@ is from 'Data.Universe.Instances.Eq'
instance (PartialOrd v, Finite k) => PartialOrd (k -> v) where
    k -> v
f leq :: (k -> v) -> (k -> v) -> Bool
`leq` k -> v
g = forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all (\k
k -> k -> v
f k
k forall a. PartialOrd a => a -> a -> Bool
`leq` k -> v
g k
k) forall a. Finite a => [a]
universeF

instance (PartialOrd v, Finite v) => PartialOrd (Endo v) where
    Endo v -> v
f leq :: Endo v -> Endo v -> Bool
`leq` Endo v -> v
g = v -> v
f forall a. PartialOrd a => a -> a -> Bool
`leq` v -> v
g