{-# options_ghc -XEmptyDataDecls -XOverlappingInstances -XScopedTypeVariables #-}
module BadGames where 

import Data.Maybe
import Iso
import Games
import BasicGames

-- /badBoolGame/
-- precondition: t is uninhabited
voidGame :: Game t
voidGame = Split (splitIso (const True)) voidGame voidGame

badBoolGame :: Game Bool
badBoolGame = Split (splitIso id)  
  (Split (splitIso id) (constGame True) voidGame) 
  (Split (splitIso id) voidGame (constGame False))
-- /End/

-- /badNatGame/
badNatGame :: Game Nat
badNatGame = Split parityIso badNatGame badNatGame
-- /End/

{-
badBoolGame2 :: Game Bool
badBoolGame2 = Split (splitIso id)
  (Split (Iso (\x -> if x then Left () else Right ()) (const True)) unitGame unitGame)
  (Split (Iso (\x -> if x then Left () else Right ()) (const False)) unitGame unitGame)
-}

badBoolGame3 :: Game Bool
badBoolGame3 = Split boolIso
  (Split (Iso (const (Left ())) (const ())) unitGame unitGame)
  (Split (Iso (const (Right())) (const ())) unitGame unitGame)