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