Skip to content

Instantly share code, notes, and snippets.

@yksym
Last active September 24, 2017 23:12
Show Gist options
  • Save yksym/4e59de6a132ca0c81541593b6d01cf83 to your computer and use it in GitHub Desktop.
Save yksym/4e59de6a132ca0c81541593b6d01cf83 to your computer and use it in GitHub Desktop.
Is it function??
{-# LANGUAGE DataKinds, TypeOperators, KindSignatures, TypeFamilies #-}
{-# LANGUAGE UndecidableInstances, FlexibleInstances, FlexibleContexts #-}
module IsFun (
Proxy
, isFun
, cntArgs
) where
import Data.Proxy
import GHC.TypeLits
type family CntArgs (a :: *) :: Nat where
CntArgs (a -> b) = 1 + CntArgs b
CntArgs a = 0
proxy' :: a -> Proxy (CntArgs a)
proxy' _ = Proxy
cntArgs :: KnownNat (CntArgs a) => a -> Integer
cntArgs x = natVal $ proxy' x
isFun :: KnownNat (CntArgs a) => a -> Bool
isFun x = cntArgs x > 0
f1 :: Int -> Int
f1 = id
f2 :: Int -> Int -> Int
f2 = const
v :: Int
v = 0
main = do
print $ isFun f1 -- a -> a の a が曖昧で数えられない
print $ isFun f2
print $ isFun v
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment