Skip to content

Instantly share code, notes, and snippets.

@neongreen
Created January 28, 2019 10:58
Show Gist options
  • Save neongreen/f9abbea45aa16db883f3e6a486153734 to your computer and use it in GitHub Desktop.
Save neongreen/f9abbea45aa16db883f3e6a486153734 to your computer and use it in GitHub Desktop.
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE TypeApplications #-}
module ApplyLast where
import Data.Text
import Data.Maybe
data Nat = Z | S Nat
data NumArgs :: Nat -> * -> * where
NAZ :: NumArgs Z a
NAS :: NumArgs n b -> NumArgs (S n) (a -> b)
type family CountArgs (f :: *) :: Nat where
CountArgs (a -> b) = S (CountArgs b)
CountArgs result = Z
class CNumArgs (numArgs :: Nat) (arrows :: *) where
getNA :: NumArgs numArgs arrows
instance CNumArgs Z a where
getNA = NAZ
instance CNumArgs n b => CNumArgs (S n) (a -> b) where
getNA = NAS getNA
type family Apply (f :: * -> *) (n :: Nat) (arrows :: *) :: * where
Apply f (S n) (a -> b) = a -> Apply f n b
Apply f Z a = f a
applyLast :: forall f fun .
(Applicative f, CNumArgs (CountArgs fun) fun)
=> fun -> Apply f (CountArgs fun) fun
applyLast = applyLast' @f (getNA :: NumArgs (CountArgs fun) fun)
applyLast' :: forall f n fun .
Applicative f
=> NumArgs n fun -> fun -> Apply f n fun
applyLast' NAZ x = pure x
applyLast' (NAS n) f = \a -> applyLast' @f n (f a)
-- well
data T = T Int Text
a' = fromJust (applyLast T 1 "hi")
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment