Skip to content

Instantly share code, notes, and snippets.

@kcsongor
Created December 4, 2017 14:13
Show Gist options
  • Save kcsongor/63b7896cdaaac46322d68f2fe65b868c to your computer and use it in GitHub Desktop.
Save kcsongor/63b7896cdaaac46322d68f2fe65b868c to your computer and use it in GitHub Desktop.
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
import GHC.TypeLits
data Proxy a = Proxy deriving Show
-- This is the traditional `fib n = fib (n - 1) + fib (n - 2)
-- exponential
class FibSlow (ind :: Nat) (fib :: Nat) | ind -> fib
instance {-# OVERLAPPING #-} FibSlow 0 1
instance {-# OVERLAPPING #-} FibSlow 1 1
instance (FibSlow (i - 1) n, FibSlow (i - 2) m, fibn ~ (n + m)) => FibSlow i fibn
fibTest1 :: FibSlow i n => Proxy i -> Proxy n
fibTest1 _ = Proxy
-- >>> fibTest1 (Proxy :: Proxy 15)
-- Proxy
-- (7.71 secs, 284,048 bytes)
-- >>> :t it
-- it :: Proxy 987
-- If constraints were cached, this would be a *lot* faster
--------------------------------------------------------------------------------
-- linear fib, a lot faster
class FibFast (i :: Nat) (b :: Nat) (c :: Nat) | i b -> c, i -> b c
instance {-# OVERLAPPING #-} FibFast 0 1 1
instance {-# OVERLAPPING #-} FibFast 1 1 2
instance (FibFast (i - 1) b c, r ~ (b + c)) => FibFast i c r
fibTest2 :: FibFast i b c => Proxy i -> Proxy b
fibTest2 _ = Proxy
-- >>> fibTest2 (Proxy :: Proxy 200)
-- Proxy
-- (0.57 secs, 136,552 bytes)
-- >>> :t it
-- it :: Proxy 453973694165307953197296969697410619233826
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment