{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE DataKinds #-}
module Agda.Utils.WithDefault where
import Control.DeepSeq
import Agda.Utils.TypeLits
data WithDefault (b :: Bool) = Default | Value !Bool
deriving (WithDefault b -> WithDefault b -> Bool
forall (b :: Bool). WithDefault b -> WithDefault b -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: WithDefault b -> WithDefault b -> Bool
$c/= :: forall (b :: Bool). WithDefault b -> WithDefault b -> Bool
== :: WithDefault b -> WithDefault b -> Bool
$c== :: forall (b :: Bool). WithDefault b -> WithDefault b -> Bool
Eq, Int -> WithDefault b -> ShowS
forall (b :: Bool). Int -> WithDefault b -> ShowS
forall (b :: Bool). [WithDefault b] -> ShowS
forall (b :: Bool). WithDefault b -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [WithDefault b] -> ShowS
$cshowList :: forall (b :: Bool). [WithDefault b] -> ShowS
show :: WithDefault b -> String
$cshow :: forall (b :: Bool). WithDefault b -> String
showsPrec :: Int -> WithDefault b -> ShowS
$cshowsPrec :: forall (b :: Bool). Int -> WithDefault b -> ShowS
Show)
instance NFData (WithDefault b) where
rnf :: WithDefault b -> ()
rnf WithDefault b
Default = ()
rnf (Value Bool
_) = ()
setDefault :: Bool -> WithDefault b -> WithDefault b
setDefault :: forall (b :: Bool). Bool -> WithDefault b -> WithDefault b
setDefault Bool
b = \case
WithDefault b
Default -> forall (b :: Bool). Bool -> WithDefault b
Value Bool
b
WithDefault b
t -> WithDefault b
t
collapseDefault :: KnownBool b => WithDefault b -> Bool
collapseDefault :: forall (b :: Bool). KnownBool b => WithDefault b -> Bool
collapseDefault = \case
w :: WithDefault b
w@WithDefault b
Default -> forall (proxy :: Bool -> *) (b :: Bool).
KnownBool b =>
proxy b -> Bool
boolVal WithDefault b
w
Value Bool
b -> Bool
b