1{-# OPTIONS_GHC -Wunused-imports #-}
2
3-- | Utilities for functors.
4
5module Agda.Utils.Functor
6 ( (<.>)
7 , for
8 , Decoration(traverseF, distributeF)
9 , dmap
10 , dget
11 -- From Data.Functor:
12 , (<$>)
13 , ($>)
14 , (<&>)
15 )
16 where
17
18import Control.Applicative ( Const(Const), getConst )
19
20import Data.Functor (($>), (<&>))
21import Data.Functor.Identity
22import Data.Functor.Compose
23
24
25infixr 9 <.>
26
27-- | Composition: pure function after functorial (monadic) function.
28(<.>) :: Functor m => (b -> c) -> (a -> m b) -> a -> m c
29(f <.> g) a = f <$> g a
30
31-- | The true pure @for@ loop.
32-- 'Data.Traversable.for' is a misnomer, it should be @forA@.
33for :: Functor m => m a -> (a -> b) -> m b
34for a b = fmap b a
35{-# INLINE for #-}
36
37-- | A decoration is a functor that is traversable into any functor.
38--
39-- The 'Functor' superclass is given because of the limitations
40-- of the Haskell class system.
41-- @traverseF@ actually implies functoriality.
42--
43-- Minimal complete definition: @traverseF@ or @distributeF@.
44class Functor t => Decoration t where
45
46 -- | @traverseF@ is the defining property.
47 traverseF :: Functor m => (a -> m b) -> t a -> m (t b)
48 traverseF f = distributeF . fmap f
49
50 -- | Decorations commute into any functor.
51 distributeF :: (Functor m) => t (m a) -> m (t a)
52 distributeF = traverseF id
53
54-- | Any decoration is traversable with @traverse = traverseF@.
55-- Just like any 'Traversable' is a functor, so is
56-- any decoration, given by just @traverseF@, a functor.
57dmap :: Decoration t => (a -> b) -> t a -> t b
58dmap f = runIdentity . traverseF (Identity . f)
59
60-- | Any decoration is a lens. @set@ is a special case of @dmap@.
61dget :: Decoration t => t a -> a
62dget = getConst . traverseF Const
63
64-- | The identity functor is a decoration.
65instance Decoration Identity where
66 traverseF f (Identity x) = Identity <$> f x
67
68-- | Decorations compose. (Thus, they form a category.)
69instance (Decoration d, Decoration t) => Decoration (Compose d t) where
70 -- traverseF . traverseF :: Functor m => (a -> m b) -> d (t a) -> m (d (t a))
71 traverseF f (Compose x) = Compose <$> traverseF (traverseF f) x
72
73-- Not a decoration are:
74--
75-- * The constant functor.
76-- * Maybe. Can only be traversed into pointed functors.
77-- * Other disjoint sum types, like lists etc.
78-- (Can only be traversed into Applicative.)
79
80-- | A typical decoration is pairing with some stuff.
81instance Decoration ((,) a) where
82 traverseF f (a, x) = (a,) <$> f x