Skip to content

Instantly share code, notes, and snippets.

@Lysxia
Created May 11, 2019 16:04
Show Gist options
  • Save Lysxia/c754f2fd6a514d66559b92469e373352 to your computer and use it in GitHub Desktop.
Save Lysxia/c754f2fd6a514d66559b92469e373352 to your computer and use it in GitHub Desktop.
{-# LANGUAGE
AllowAmbiguousTypes,
FlexibleContexts,
FlexibleInstances,
MultiParamTypeClasses,
UndecidableInstances,
TypeApplications
#-}
import Control.Category hiding ((.), id)
import Control.Arrow
import Data.Kind (Type)
-- Turn (a -> (b -> (c -> ...))) into (a `r` (b `r` (c `r` ...)))
class Arrowfy (r :: Type -> Type -> Type) x y where
arrowfy :: x -> y
instance {-# OVERLAPPING #-} (Arrow r, Arrowfy r b z, y ~ r a z) => Arrowfy r (a -> b) y where
arrowfy f = arr (arrowfy @r @b @z . f)
instance (x ~ y) => Arrowfy r x y where
arrowfy = id
-- Dummy arrow
data a :-> b = PA
instance Category (:->) where -- ...
instance Arrow (:->) where -- ...
test :: Int :-> (Int :-> Int)
test = arrowfy (+)
---
-- Turn (a -> (b -> (c -> ... (... -> z) ...))) into ((a, (b, (c, ...))) -> z)
class Uncurry x y z where
uncurry_ :: x -> y -> z
instance {-# OVERLAPPING #-} (Uncurry (b -> c) yb z, y ~ (a, yb)) => Uncurry (a -> b -> c) y z where
uncurry_ f (a, yb) = uncurry_ (f a) yb
instance (a ~ y, b ~ z) => Uncurry (a -> b) y z where
uncurry_ = id
testUncurry :: (Int, Int) -> Int
testUncurry = uncurry_ (+)
--
testUncurry2 :: (Int, (Int, (Int, Int))) :-> Int
testUncurry2 = arr (uncurry_ (\a b c d -> a + b + c + d))
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment