Skip to content

Instantly share code, notes, and snippets.

@Lysxia
Last active January 24, 2022 17:09
Show Gist options
  • Star 1 You must be signed in to star a gist
  • Fork 0 You must be signed in to fork a gist
  • Save Lysxia/cf47807bbbcbb572896b350d66162a25 to your computer and use it in GitHub Desktop.
Save Lysxia/cf47807bbbcbb572896b350d66162a25 to your computer and use it in GitHub Desktop.
{-# LANGUAGE TypeFamilies, DataKinds, ConstraintKinds, UndecidableInstances, TypeApplications, ScopedTypeVariables #-}
module Countdown where
import Data.Proxy
import GHC.TypeNats
import Data.Kind
import qualified Fcf as F
data C2 :: Nat -> F.Exp Constraint
type instance F.Eval (C2 x) =
(KnownNat x,
IsBool (F.Eval (x F.> 0)),
F.Eval (F.If (F.Eval (x F.> 0))
(C2 (x - 1))
(F.Pure (() :: Constraint))))
class IsBool b where
getBool :: SBool b
instance IsBool 'True where
getBool = STrue
instance IsBool 'False where
getBool = SFalse
data SBool (a :: Bool) where
SFalse :: SBool 'False
STrue :: SBool 'True
countdown :: forall n. F.Eval (C2 n) => Proxy n -> String
countdown _ =
case getBool @(F.Eval (n F.> 0)) of
STrue -> show (natVal @n Proxy) ++ " " ++ countdown @(n-1) Proxy
SFalse -> "boom"
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment