-- SPDX-FileCopyrightText: 2021 Oxhead Alpha -- SPDX-License-Identifier: LicenseRef-MIT-OA {-# LANGUAGE NoImplicitPrelude #-} -- | This module replaces the monomorphic boolean operators from "Prelude" -- with a set of polymorphic operators. module Morley.Prelude.Boolean ( Boolean(..) , ApplicativeBoolean(..) ) where import Universum hiding ((&&), (||)) import Universum qualified -- | Generalized boolean operators. class Boolean a where (&&) :: a -> a -> a (||) :: a -> a -> a infixr 3 && infixr 2 || instance Boolean Bool where (&&) = (Universum.&&) (||) = (Universum.||) -- | A newtype for deriving a 'Boolean' instance for any 'Applicative' type -- constructor using @DerivingVia@. newtype ApplicativeBoolean f bool = ApplicativeBoolean (f bool) deriving newtype (Functor, Applicative) instance (Applicative f, Boolean bool) => Boolean (ApplicativeBoolean f bool) where (&&) = liftA2 (&&) (||) = liftA2 (||) deriving via (ApplicativeBoolean IO bool) instance Boolean bool => Boolean (IO bool) deriving via (ApplicativeBoolean ((->) a) bool) instance Boolean bool => Boolean (a -> bool)