Skip to content

Instantly share code, notes, and snippets.

@memowe
Last active July 11, 2024 10:18
Show Gist options
  • Save memowe/cbc92aecfc2347389e6d6441e7396649 to your computer and use it in GitHub Desktop.
Save memowe/cbc92aecfc2347389e6d6441e7396649 to your computer and use it in GitHub Desktop.
-- On the "on" operator of Data.Function
-- https://hackage.haskell.org/package/base/docs/Data-Function.html#v:on
--
-- on :: (b -> b -> c) -> (a -> b) -> a -> a -> c
-- with
-- (op `on` f) x y = f x `op` f y
--
-- Question: is there any way to create a vararg combinator?
-- https://wiki.haskell.org/Varargs
-- onN :: (b -> b -> ... -> c) -> (a -> b) -> a -> a -> ... -> c
on1 :: (b -> c) -> (a -> b) -> a -> c
on1 f g = (. g) f
on2 :: (b -> b -> c) -> (a -> b) -> a -> a -> c
on2 f g = (. g) . on1 f g
on3 :: (b -> b -> b -> c) -> (a -> b) -> a -> a -> a -> c
on3 f g = ((. g) .) . on2 f g
on4 :: (b->b->b->b->c) -> (a -> b) -> a->a->a->a->c
on4 f g = (((. g) .) .) . on3 f g
-- = (((. g) .) .) . ((. g) .) . on2 f g
-- = (((. g) .) .) . ((. g) .) . (. g) . on1 f g
-- = (((. g) .) .) . ((. g) .) . (. g) . (. g) f
@memowe
Copy link
Author

memowe commented Jul 11, 2024

"Work" in progress:

{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE UndecidableInstances #-}

-- Wanted:
-- (on1 :: (b -> c)             -> (a -> b) -> a              -> c)
--  on2 :: (b -> b -> c)        -> (a -> b) -> a -> a         -> c
--  onN :: (b -> b -> ... -> c) -> (a -> b) -> a -> a -> ...  -> c
class On a b x y | a b x -> y where
  on :: (b -> x) -> (a -> b) -> y

instance On a b (b -> c) (a -> a -> c) where
  on f g x y = f (g x) (g y)

instance On a b c d => On a b (b -> c) (a -> d) where
  on f g x = _ -- on f g x . g

@memowe
Copy link
Author

memowe commented Jul 11, 2024

meooow on #haskell @ FP discord:

class On r1 ab r2 where
  on_ :: r1 -> ab -> r2

newtype I a = I { unI :: a }

instance On c ab (I c) where
  on_ c _ = I c

instance On r1 (a -> b) r2 => On (b -> r1) (a -> b) (a -> r2) where
  on_ bc ab a = on_ (bc (ab a)) ab

ex1 :: Bool
ex1 = unI $ on_ eq3 plus1 (0 :: Int) (1 :: Int) (2 :: Int)
  where
    eq3 :: Int -> Int -> Int -> Bool
    eq3 x y z = x == y && y == z
    plus1 :: Int -> Int
    plus1 = (+1)

Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment