{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}

{-# OPTIONS_GHC -fplugin=IfSat.Plugin #-}

module M1 where

-- base

import Data.Kind
  ( Type )

-- if-instance

import Data.Constraint.If
  ( IfSat(ifSat) )

--------------------------------------------------------------------------------


showFun :: forall (a :: Type). IfSat ( Show ( a -> a ) ) => ( a -> a ) -> String
showFun :: forall a. IfSat (Show (a -> a)) => (a -> a) -> String
showFun = forall (ct :: Constraint) r.
IfSat ct =>
((IsSat ct ~ 'True, ct) => r) -> ((IsSat ct ~ 'False) => r) -> r
ifSat @( Show (a -> a) ) (IsSat (Show (a -> a)) ~ 'True, Show (a -> a)) =>
(a -> a) -> String
forall a. Show a => a -> String
show ( \ a -> a
_ -> String
"<<function>>" )

test1 :: ( Bool -> Bool ) -> String
test1 :: (Bool -> Bool) -> String
test1 Bool -> Bool
fun = (Bool -> Bool) -> String
forall a. IfSat (Show (a -> a)) => (a -> a) -> String
showFun Bool -> Bool
fun