Skip to content

Instantly share code, notes, and snippets.

@poscat0x04
Created May 2, 2020 08:16
Show Gist options
  • Star 0 You must be signed in to star a gist
  • Fork 0 You must be signed in to fork a gist
  • Save poscat0x04/b7bc9544e28442b4b777f87cb5a147a4 to your computer and use it in GitHub Desktop.
Save poscat0x04/b7bc9544e28442b4b777f87cb5a147a4 to your computer and use it in GitHub Desktop.
{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
import GHC.TypeLits
data NPlus = One | Suc NPlus
class Applicable (n :: NPlus) a f | f n -> a where
type ApplyAt n a f :: *
inject :: a -> f -> ApplyAt n a f
instance Applicable One a (a -> b) where
type ApplyAt One a (a -> b) = b
inject a f = f a
instance (Applicable n a c) => Applicable (Suc n) a (b -> c) where
type ApplyAt (Suc n) a (b -> c) = b -> ApplyAt n a c
inject a f = \x -> inject @n a (f x)
type family ToNPlus (n :: Nat) :: NPlus where
ToNPlus 0 = TypeError (Text "0 is not a positive integer")
ToNPlus 1 = One
ToNPlus n = Suc (ToNPlus (n - 1))
main = do
putStrLn $ (inject @(ToNPlus 1) "a" (\a b c -> "a: " <> a <> "\nb: " <> b <> "\nc: " <> c <> "\n")) "b" "c"
putStrLn $ (inject @(ToNPlus 2) "a" (\a b c -> "a: " <> a <> "\nb: " <> b <> "\nc: " <> c <> "\n")) "b" "c"
putStrLn $ (inject @(ToNPlus 3) "a" (\a b c -> "a: " <> a <> "\nb: " <> b <> "\nc: " <> c <> "\n")) "b" "c"
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment