{-# LANGUAGE FlexibleInstances      #-}
{-# LANGUAGE MultiParamTypeClasses  #-}
{-# LANGUAGE TypeOperators          #-}
{-# LANGUAGE OverlappingInstances   #-}
{-# OPTIONS -fno-warn-orphans       #-}

-----------------------------------------------------------------------------
-- |
-- Module      :  Generics.EMGM.Data.Bool
-- Copyright   :  (c) 2008 Universiteit Utrecht
-- License     :  BSD3
--
-- Maintainer  :  generics@haskell.org
-- Stability   :  experimental
-- Portability :  non-portable
--
-- Summary: Generic representation and instances for 'Bool'.
--
-- This module exports the reusable components of the 'Bool'
-- representation. These include the embedding-projection pair used in a type
-- representation as well as the type representation of 'Bool' for
-- 'Generic'.
--
-- This module also exports the instance for the representation dispatcher
-- 'Rep'.
-----------------------------------------------------------------------------

module Generics.EMGM.Data.Bool (

  -- * Embedding-projection pair
  epBool,

  -- * Representation
  rBool,
) where

import Generics.EMGM.Common

-----------------------------------------------------------------------------
-- Embedding-projection pair
-----------------------------------------------------------------------------

fromBool :: Bool -> Unit :+: Unit
fromBool False = L Unit
fromBool True  = R Unit

toBool :: Unit :+: Unit -> Bool
toBool (L Unit) = False
toBool (R Unit) = True

-- | Embedding-projection pair for @Bool@
epBool :: EP Bool (Unit :+: Unit)
epBool = EP fromBool toBool

-----------------------------------------------------------------------------
-- Representation values
-----------------------------------------------------------------------------

conFalse, conTrue :: ConDescr
conFalse = ConDescr "False" 0 [] Nonfix
conTrue  = ConDescr "True"  0 [] Nonfix

-- | Representation for @Bool@ in 'Generic'
rBool :: (Generic g) => g Bool
rBool = rtype epBool (rcon conFalse runit `rsum` rcon conTrue runit)

-----------------------------------------------------------------------------
-- Instance declarations
-----------------------------------------------------------------------------

instance (Generic g) => Rep g Bool where
  rep = rBool