Skip to content

Instantly share code, notes, and snippets.

@paf31
Created November 24, 2015 19:16
Show Gist options
  • Star 3 You must be signed in to star a gist
  • Fork 0 You must be signed in to fork a gist
  • Save paf31/15800b8a1cd01368c012 to your computer and use it in GitHub Desktop.
Save paf31/15800b8a1cd01368c012 to your computer and use it in GitHub Desktop.
Profunctor-based Traversable
module Main where
import Prelude
import Data.Maybe
import Data.Either
import Data.Tuple
import Data.List
import Data.Profunctor
import Data.Profunctor.Strong
import Data.Profunctor.Choice
class (Strong p, Choice p) <= Both p where
both :: forall a b c d. p a b -> p c d -> p (Tuple a c) (Tuple b d)
class (Both p) <= None p where
none :: forall a. p a a
type Traversal a b c d = forall p. (None p) => p a b -> p c d
class Traversable t where
traverse :: forall a b. Traversal a b (t a) (t b)
instance traverseMaybe :: Traversable Maybe where
traverse = dimap (maybe (Left unit) Right) (either (const Nothing) Just) <<< right
instance traverseEither :: Traversable (Either a) where
traverse = right
instance traverseTuple :: Traversable (Tuple a) where
traverse = second
instance traverseList :: Traversable List where
traverse pab = dimap uncons (maybe Nil (uncurry Cons)) (traverse (both pab (traverse pab)))
where
uncons Nil = Nothing
uncons (Cons x xs) = Just (Tuple x xs)
@Icelandjack
Copy link

Icelandjack commented Oct 2, 2017

This is a very cool application of profunctors

Similar to Varying lens properties by instance we can vary the power needed

class Trav t where
  type Constr t :: (Type -> Type -> Type) -> Constraint

  trav :: Constr t p => p a a' -> p (t a) (t a')

instance Trav Maybe where
  type Constr Maybe = Choice

  trav :: Choice p => p a a' -> p (Maybe a) (Maybe a')
  trav = ..

instance Trav ((,) a) where
  type Constr ((,) a) = Strong

  trav :: Strong p => p b b' -> p (a, b) (a, b')
  trav = second'

instance Trav [] where
  type Constr [] = Both

  trav :: Both p => p a a' -> p [a] [a']
  trav pab = ..

@Icelandjack
Copy link

Also you don't seem to make use of none :: None p => p a a anywhere?

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