{-# LANGUAGE LinearTypes #-}
{-# LANGUAGE NoImplicitPrelude #-}
module Data.Bool.Linear
  ( 
    Bool (..),
    
    (&&),
    (||),
    not,
    otherwise,
  )
where
import Prelude (Bool (..), otherwise)
(&&) :: Bool %1 -> Bool %1 -> Bool
Bool
False && :: Bool %1 -> Bool %1 -> Bool
&& Bool
False = Bool
False
Bool
False && Bool
True = Bool
False
Bool
True && Bool
x = Bool
x
infixr 3 && 
(||) :: Bool %1 -> Bool %1 -> Bool
Bool
True || :: Bool %1 -> Bool %1 -> Bool
|| Bool
False = Bool
True
Bool
True || Bool
True = Bool
True
Bool
False || Bool
x = Bool
x
infixr 2 || 
not :: Bool %1 -> Bool
not :: Bool %1 -> Bool
not Bool
False = Bool
True
not Bool
True = Bool
False