Using type families, we can define the function fold over a type and the underlying algebra for that type represented as an n-tuple of functions and constant values. This permits the definition of a generalized foldr function, defined in the Foldable type class:
import Data.Set (Set)
import Data.Map (Map)
import qualified Data.Set as S
import qualified Data.Map as M
class Foldable m where
type Algebra m b :: *
fold :: Algebra m b -> m -> b
instance (Ord a) => Foldable (Set a) where
type Algebra (Set a) b = (b, a -> b -> b)
fold = uncurry $ flip S.fold
instance (Ord k) => Foldable (Map k a) where
type Algebra (Map k a) b = (b, k -> a -> b -> b)
fold = uncurry $ flip M.foldWithKey
Similarly, constraint kinds permit the definition of a generalized map function. The map function differs from fmap by considering each value field of an algebraic data type:
class Mappable m where
type Contains m :: *
type Mapped m r b :: Constraint
map :: (Mapped m r b) => (Contains m -> b) -> m -> r
instance (Ord a) => Mappable (Set a) where
type Contains (Set a) = a
type Mapped (Set a) r b = (Ord b, r ~ Set b)
map = S.map
instance (Ord k) => Mappable (Map k a) where
type Contains (Map k a) = (k, a)
type Mapped (Map k a) r b = (Ord k, r ~ Map k b)
map = M.mapWithKey . curry
From the user's perspective, neither function is particularly friendly. In particular, neither technique permits the definition of curried functions. This means that the user cannot easily apply either fold or the mapped function partially. What I would like is a type-level function that curries tuples of functions and values, in order to generate curried versions of the above. Thus, I would like to write something approximating the following type-function:
Curry :: Product -> Type -> Type
Curry () m = m
Curry (a × as) m = a -> (Curry as m b)
If so, we could generate a curried fold function from the underlying algebra. For instance:
fold :: Curry (Algebra [a] b) ([a] -> b)
≡ fold :: Curry (b, a -> b -> b) ([a] -> b)
≡ fold :: b -> (Curry (a -> b -> b)) ([a] -> b)
≡ fold :: b -> (a -> b -> b -> (Curry () ([a] -> b))
≡ fold :: b -> ((a -> b -> b) -> ([a] -> b))
map :: (Mapped (Map k a) r b) => (Curry (Contains (Map k a)) b) -> Map k a -> r
≡ map :: (Mapped (Map k a) r b) => (Curry (k, a) b) -> Map k a -> r
≡ map :: (Mapped (Map k a) r b) => (k -> (Curry (a) b) -> Map k a -> r
≡ map :: (Mapped (Map k a) r b) => (k -> (a -> Curry () b)) -> Map k a -> r
≡ map :: (Mapped (Map k a) r b) => (k -> (a -> b)) -> Map k a -> r
I know that Haskell doesn't have type functions, and the proper representation of the n-tuple would probably be something like a type-level length-indexed list of types. Is this possible?
EDIT: For completeness, my current attempt at a solution is attached below. I am using empty data types to represent products of types, and type families to represent the function Curry, above. This solution appears to work for the map function, but not the fold function. I believe, but am not certain, that Curry is not being reduced properly when type checking.
data Unit
data Times a b
type family Curry a m :: *
type instance Curry Unit m = m
type instance Curry (Times a l) m = a -> Curry l m
class Foldable m where
type Algebra m b :: *
fold :: Curry (Algebra m b) (m -> b)
instance (Ord a) => Foldable (Set a) where
type Algebra (Set a) b = Times (a -> b -> b) (Times b Unit)
fold = S.fold
instance (Ord k) => Foldable (Map k a) where
type Algebra (Map k a) b = Times (k -> a -> b -> b) (Times b Unit)
fold = M.foldWithKey
class Mappable m where
type Contains m :: *
type Mapped m r b :: Constraint
map :: (Mapped m r b) => Curry (Contains m) b -> m -> r
instance (Ord a) => Mappable (Set a) where
type Contains (Set a) = Times a Unit
type Mapped (Set a) r b = (Ord b, r ~ Set b)
map = S.map
instance (Ord k) => Mappable (Map k a) where
type Contains (Map k a) = Times k (Times a Unit)
type Mapped (Map k a) r b = (Ord k, r ~ Map k b)
map = M.mapWithKey
Ok, if I understand you correctly, you can create inconvenient folds, but want to have convenient curried folds.
Below is an explanation how to achieve this as a separate step. Yes, it can also be done all at once, I've done something similar before. However, I think the separate phase makes it clearer what's going on.
We need the following language extensions:
{-# LANGUAGE TypeFamilies, TypeOperators, FlexibleInstances #-}
I'm using the following product and unit types:
data U = U
data a :*: b = a :*: b
infixr 8 :*:
As an example, let's assume we have an inconvenient version of a fold on lists:
type ListAlgType a r = (U -> r)
:*: (a :*: r :*: U -> r)
:*: U
inconvenientFold :: ListAlgType a r -> [a] -> r
inconvenientFold (nil :*: cons :*: U) [] = nil U
inconvenientFold a#(nil :*: cons :*: U) (x : xs) = cons (x :*: inconvenientFold a xs :*: U)
We have a nested product type, and we want to curry both levels. I'm defining two type classes for this, one for each layer. (It might be doable with one more general function, I haven't tried in this case.)
class CurryInner a where
type CurryI a k :: *
curryI :: (a -> b) -> CurryI a b
uncurryI :: CurryI a b -> a -> b
class CurryOuter a where
type CurryO a k :: *
curryO :: (a -> b) -> CurryO a b
uncurryO :: CurryO a b -> (a -> b) -- not really required here
Each type class implements the isomorphism between the curried and uncurried types. The type classes look identical, but CurryOuter will call CurryInner for each component of the outer nested tuple.
The instances are relatively straightforward:
instance CurryInner U where
type CurryI U k = k
curryI f = f U
uncurryI x = \ U -> x
instance CurryInner ts => CurryInner (t :*: ts) where
type CurryI (t :*: ts) k = t -> CurryI ts k
curryI f = \ t -> curryI (\ ts -> f (t :*: ts))
uncurryI f = \ (t :*: ts) -> uncurryI (f t) ts
instance CurryOuter U where
type CurryO U k = k
curryO f = f U
uncurryO x = \ U -> x
instance (CurryInner a, CurryOuter ts) => CurryOuter ((a -> b) :*: ts) where
type CurryO ((a -> b) :*: ts) k = CurryI a b -> CurryO ts k
curryO f = \ t -> curryO (\ ts -> f (uncurryI t :*: ts))
uncurryO f = \ (t :*: ts) -> uncurryO (f (curryI t)) ts
That's it. Note that
*Main> :kind! CurryO (ListAlgType A R) ([A] -> R)
CurryO (ListAlgType A R) ([A] -> R) :: *
= R -> (A -> R -> R) -> [A] -> R
(for suitably defined placeholder types A and R). We can use it as follows:
*Main> curryO inconvenientFold 0 (+) [1..10]
55
Edit: I now see you're actually only asking about currying the outer layer. You then only need one class, but can use the same idea. I used this example because I had written something for a sum-of-product based generic programming library which needed two levels of currying before, and thought at first you are in the same setting.
Ok, I think my other answer isn't actually really an answer to your question. Sorry for that.
In your final code, compare the types of fold and map:
fold :: Curry (Algebra m b) (m -> b)
map :: (Mapped m r b) => Curry (Contains m) b -> m -> r
There's a substantial difference here. The type of fold is just a type family application, whereas the type of map contains the final m -> r, mentioning the class parameter m. So in the case of map, it's easy for GHC to learn at which type you want to instance the class from the context.
Not so in the case of fold, unfortunately, because type families need not be injective, and therefore aren't easy to invert. So by seeing a particular type you use fold at, it's impossible for GHC to infer what m is.
The standard solution to this problem is to use a proxy argument that fixes the type of m, by defining
data Proxy m = P
and then giving fold this type instead:
fold :: Proxy m -> Curry (Algebra m b) (m -> b)
You have to adapt the instances to take and discard the proxy argument. Then you can use:
fold (P :: Proxy (Set Int)) (+) 0 (S.fromList [1..10])
or similar to call the fold function on sets.
To see more clearly why this situation is difficult for GHC to solve, consider this toy example instead:
class C a where
type F a :: *
f :: F a
instance C Bool where
type F Bool = Char -> Char
f = id
instance C () where
type F () = Char -> Char
f = toUpper
Now, if you call f 'x', there's no meaningful way for GHC to detect which instance you meant. The proxy would help here as well.
A type-level list is exactly what you need! You got very close, but you need the full power of both DataKinds and ScopedTypeVariables for this to work properly:
{-# LANGUAGE ConstraintKinds, DataKinds, FlexibleContexts, FlexibleInstances, TypeFamilies, TypeOperators, ScopedTypeVariables #-}
import GHC.Exts (Constraint)
import Data.Set (Set)
import Data.Map (Map)
import qualified Data.Set as S
import qualified Data.Map as M
-- | A "multifunction" from a list of inhabitable types to an inhabitable type (curried from the start).
type family (->>) (l :: [*]) (y :: *) :: *
type instance '[] ->> y = y
type instance (x ': xs) ->> y = x -> (xs ->> y)
class Foldable (m :: *) where
type Algebra m (b :: *) :: [*]
fold :: forall (b :: *). Algebra m b ->> (m -> b)
instance (Ord a) => Foldable (Set a) where
type Algebra (Set a) b = '[(a -> b -> b), b]
fold = S.fold :: forall (b :: *). (a -> b -> b) -> b -> Set a -> b
instance (Ord k) => Foldable (Map k a) where
type Algebra (Map k a) b = '[(k -> a -> b -> b), b]
fold = M.foldWithKey :: forall (b :: *). (k -> a -> b -> b) -> b -> Map k a -> b
class Mappable m where
type Contains m :: [*]
type Mapped m (b :: *) (r :: *) :: Constraint
map :: forall (b :: *) (r :: *). Mapped m b r => (Contains m ->> b) -> m -> r
instance (Ord a) => Mappable (Set a) where
type Contains (Set a) = '[a]
type Mapped (Set a) b r = (Ord b, r ~ Set b)
map = S.map :: forall (b :: *). (Ord b) => (a -> b) -> Set a -> Set b
instance (Ord k) => Mappable (Map k a) where
type Contains (Map k a) = '[k, a]
type Mapped (Map k a) b r = r ~ Map k b
map = M.mapWithKey :: forall (b :: *). (k -> a -> b) -> Map k a -> Map k b
Related
As I understand it, each van Laarhoven optic type can be defined by a constraint on a type constructor:
type Lens s t a b = forall f. Functor f => (a -> f b) -> s -> f t
type Traversal s t a b = forall f. Applicative f => (a -> f b) -> s -> f t
-- etc.
If we choose Monad as the constraint, does it form some kind of "optic" in a meaningful way?
type Something s t a b = forall f. Monad f => (a -> f b) -> s -> f t
My intuition is that the Monad constraint might be too restrictive to get any value out of a structure like this: since the Const functor is not a Monad, we can't do the trick of specializing f to Const in order to derive a view-like function. Still, we can do some things with this Something type; it's just not clear to me if we can do anything particularly useful with it.
The reason I'm curious is because the type of a van Laarhoven optic is suspiciously similar to the type of a function that modifies a "mutable reference" type like IORef. For example, we can easily implement
modifyIORefM :: MonadIO m => IORef a -> (a -> m a) -> () -> m ()
which, when partially-applied to an IORef, has the shape
type SomethingIO s t a b = forall f. MonadIO f => (a -> f b) -> s -> f t
where a = b and s = t = (). I'm not sure whether this is a meaningful or meaningless coincidence.
Practically speaking, such an optic is a slightly inconvenient Traversal.
That's because, practically speaking, we use a Traversal:
type Traversal s t a b = forall f. (Applicative f) => (a -> f b) -> (s -> f t)
for two things. Getting a list of as from an s, which we can do with the Const functor:
toListOf :: Traversal s t a b -> s -> [a]
toListOf t = getConst . t (Const . (:[]))
and replacing the as with bs to turn the s into a t. One method is to use the State functor, and ignoring issues with matching the counts of as and bs, we have:
setListOf :: Traversal s t a b -> [b] -> s -> t
setListOf t bs s = evalState (t (\a -> state (\(b:bs) -> (b, bs))) s) bs
If we instead have an optic using a Monad constraint:
type TraversalM s t a b = forall f. (Monad f) => (a -> f b) -> (s -> f t)
we can still perform these two operations. Since State is a monad, the setListOf operation can use the same implementation:
setListOfM :: Traversal s t a b -> [b] -> s -> t
setListOfM t bs s = evalState (t (\a -> state (\(b:bs) -> (b, bs))) s) bs
For toListOf, there's no Monad instance for Const [a], but we can use a Writer monad to extract the a values, as long as we have a dummy b value to make the type checker happy:
toListOfM :: TraversalM s t a b -> b -> s -> [a]
toListOfM t dummy_b s = execWriter (t (\a -> tell [a] >> pure dummy_b) s)
or, since Haskell has bottom:
toListOfM' :: TraversalM s t a b -> s -> [a]
toListOfM' t s = execWriter (t (\a -> tell [a] >> pure undefined) s)
Self-contained code:
import Data.Functor.Const
import Control.Monad.State
import Control.Monad.Writer
type Traversal s t a b = forall f. (Applicative f) => (a -> f b) -> (s -> f t)
toListOf :: Traversal s t a b -> s -> [a]
toListOf t = getConst . t (Const . (:[]))
setListOf :: Traversal s t a b -> [b] -> s -> t
setListOf t bs s = evalState (t (\a -> state (\(b:bs) -> (b, bs))) s) bs
type TraversalM s t a b = forall f. (Monad f) => (a -> f b) -> (s -> f t)
toListOfM :: TraversalM s t a b -> b -> s -> [a]
toListOfM t dummy_b s = execWriter (t (\a -> tell [a] >> pure dummy_b) s)
toListOfM' :: TraversalM s t a b -> s -> [a]
toListOfM' t s = execWriter (t (\a -> tell [a] >> pure undefined) s)
setListOfM :: TraversalM s t a b -> [b] -> s -> t
setListOfM t bs s = evalState (t (\a -> state (\(b:bs) -> (b, bs))) s) bs
listItems :: Traversal [a] [b] a b
listItems = traverse
listItemsM :: TraversalM [a] [b] a b
listItemsM = mapM
main = do
-- as a getter
print $ toListOf listItems [1,2,3]
print $ toListOfM listItemsM 99 [1,2,3] -- dummy value
print $ toListOfM' listItemsM [1,2,3] -- use undefined
-- as a setter
print $ setListOf listItems [4,5,6] [1,2,3]
print $ setListOfM listItemsM [4,5,6] [1,2,3]
I've been trying to write a custom Optics data structure that generalises Lenses, Prisms and Traversals. My data structure looks like this:
data Optic m a b = Optic { view :: a -> m b
, over :: a -> (b -> b) -> a
}
I want to write a function that composes two Optics, optic1 :: Optic m a b and optic2 :: Optic n b c to produce an Optic containing view :: a -> m (n c) and over :: a -> (c -> c) -> a.
In my head, the type of this composed Optic would be Optic (m n) a c, but this doesn't work - GHC will complain that m has one too many type arguments and n one too few.
Here's my non-compiling implementation of the compose function:
compose :: Optic m a b -> Optic n b c -> (m b -> (b -> n c) -> m (n c)) -> Optic (m n) a c
compose optic1 optic2 glue = Optic { view = viewCompose (view optic1) (view optic2) glue
, over = overCompose (over optic1) (over optic2)
}
viewCompose :: (a -> m b) -> (b -> n c) -> (m b -> (b -> n c) -> m (n c)) -> a -> m (n c)
viewCompose view1 view2 glue x = glue (view1 x) view2
overCompose :: (a -> (b -> b) -> a) -> (b -> (c -> c) -> b) -> a -> (c -> c) -> a
overCompose over1 over2 x f = over1 x (\y -> over2 y f)
The GHC error messages are:
optic.hs:7:83: error:
• Expecting one fewer argument to ‘m n’
Expected kind ‘* -> *’, but ‘m n’ has kind ‘*’
• In the first argument of ‘Optic’, namely ‘m n’
In the type signature:
compose :: Optic m a b
-> Optic n b c -> (m b -> (b -> n c) -> m (n c)) -> Optic (m n) a c
optic.hs:7:85: error:
• Expecting one more argument to ‘n’
Expected a type, but ‘n’ has kind ‘* -> *’
• In the first argument of ‘m’, namely ‘n’
In the first argument of ‘Optic’, namely ‘m n’
In the type signature:
compose :: Optic m a b
-> Optic n b c -> (m b -> (b -> n c) -> m (n c)) -> Optic (m n) a c
If I create an optic of type Optic Maybe Int Int, GHC understands that the first type argument has kind * -> * and doesn't complain about insufficient arguments. But I can't figure out how to combine types together to create another type of kind * -> *.
Is there any way (with or without language extensions) to express something like:
Optic (forall t. m (n t)) a c
As per #chi's comment, Haskell doesn't directly support type-level lambdas. So, while there exists a type named Maybe of kind * -> * which directly represents the type-level lambda \a ~> Maybe a, there's no corresponding type directly representing the type-level lambda \a ~> Maybe (Maybe a).
This means that given your defined type for the field view:
view :: a -> m b
it is impossible to find an optic Optic m a b for any type m that would satisfy:
view :: a -> Maybe (Maybe b) -- impossible
You must instead use some kind of encoding for these types. The Compose newtype imported from Data.Functor.Compose is one alternative. It's definition is:
newtype Compose m n a = Compose (m (n a))
It basically wraps up the type lambda \a ~> m (n a) which has no direct Haskell representation into a type lambda \a ~> (Compose m n) a whose direct Haskell representation is simply Compose m n : * -> *.
The drawback is that it will introduce a non-uniformity in your types -- there'll be "plain" optics like Optic Maybe Int Int and then "composed" optics, like Optic (Compose Maybe Maybe) Int Int. You can use coerce to work around this inconvenience in most cases.
The appropriate definition of compose using the Compose newtype would look something like:
type Glue m n b c = m b -> (b -> n c) -> m (n c)
compose :: Optic m a b -> Optic n b c -> Glue m n b c -> Optic (Compose m n) a c
compose optic1 optic2 glue
= Optic { view = viewCompose (view optic1) (view optic2) glue
, over = overCompose (over optic1) (over optic2)
}
where
viewCompose view1 view2 glue x = Compose $ glue (view1 x) view2
overCompose over1 over2 x f = over1 x (\y -> over2 y f)
and for a typical Maybe-based optic:
_Left :: Optic Maybe (Either a b) a
_Left = Optic v o
where v (Left x) = Just x
v (Right _) = Nothing
o (Left x) f = Left (f x)
o (Right y) _ = Right y
a composed optic might look like:
_Left2 = compose _Left _Left (flip fmap)
Using it directly will introduce a Compose wrapper:
> view _Left2 (Left (Left "xxx"))
Compose (Just (Just "xxx"))
but you can coerce the result to avoid explicit unwrapping, particularly helpful if there are multiple nested Compose layers:
λ> import Data.Coerce
λ> _Left4 = compose _Left2 _Left2 (flip fmap)
λ> :t _Left4
_Left4
:: Optic
(Compose (Compose Maybe Maybe) (Compose Maybe Maybe))
(Either (Either (Either (Either c b4) b5) b6) b7)
c
λ> view _Left4 (Left (Left (Left (Left True))))
Compose (Compose (Just (Just (Compose (Just (Just True))))))
λ> coerce $ view _Left4 (Left (Left (Left (Left True)))) :: Maybe (Maybe (Maybe (Maybe Bool)))
Just (Just (Just (Just True)))
The full code:
import Data.Coerce
import Data.Functor.Compose
data Optic m a b = Optic { view :: a -> m b
, over :: a -> (b -> b) -> a
}
type Glue m n b c = m b -> (b -> n c) -> m (n c)
compose :: Optic m a b -> Optic n b c -> Glue m n b c -> Optic (Compose m n) a c
compose optic1 optic2 glue
= Optic { view = viewCompose (view optic1) (view optic2) glue
, over = overCompose (over optic1) (over optic2)
}
where
viewCompose view1 view2 glue x = Compose $ glue (view1 x) view2
overCompose over1 over2 x f = over1 x (\y -> over2 y f)
_Left :: Optic Maybe (Either a b) a
_Left = Optic v o
where v (Left x) = Just x
v (Right _) = Nothing
o (Left x) f = Left (f x)
o (Right y) _ = Right y
_Left2 :: Optic (Compose Maybe Maybe) (Either (Either c b1) b2) c
_Left2 = compose _Left _Left (flip fmap)
_Left4 :: Optic (Compose (Compose Maybe Maybe) (Compose Maybe Maybe)) (Either (Either (Either (Either c b1) b2) b3) b4) c
_Left4 = compose _Left2 _Left2 (flip fmap)
main = do
print $ view _Left4 (Left (Left (Left (Left True))))
print $ (coerce $ view _Left4 (Left (Left (Left (Left True)))) :: Maybe (Maybe (Maybe (Maybe Bool))))
I am trying to understand why adding id in the last line of the sequence below removes the monadic aspect:
Prelude> :t id
id :: a -> a
Prelude> :t Control.Monad.liftM2
Control.Monad.liftM2
:: Monad m => (a1 -> a2 -> r) -> m a1 -> m a2 -> m r
Prelude> :t (==)
(==) :: Eq a => a -> a -> Bool
Prelude> :t Control.Monad.liftM2 (==)
Control.Monad.liftM2 (==)
:: (Monad m, Eq a) => m a -> m a -> m Bool
Prelude> :t Control.Monad.liftM2 (==) id
Control.Monad.liftM2 (==) id :: Eq a => (a -> a) -> a -> Bool
Prelude>
How does adding id :: a -> a change the signature in the way it does in the last line ?
You’re fixing the type to a particular Monad instance, namely the “function reader” monad (instance Monad ((->) a)).
id :: a -> a and you are attempting to use it as an argument to a parameter of type m a, so:
m a ~ a -> a
m a ~ (->) a a
m a ~ ((->) a) a
m ~ (->) a
a ~ a
The remainder of the signature is:
m a -> m Bool
And since m ~ (->) a, the resulting type is:
(->) a a -> (->) a Bool
(a -> a) -> (a -> Bool)
(a -> a) -> a -> Bool
(Plus the Eq a constraint from the use of ==.)
This is useful in pointfree code, particularly using the Applicative instance, since you can implicitly “spread” the argument of a function to subcomputations:
nextThree = (,,) <$> (+ 1) <*> (+ 2) <*> (+ 3)
-- or
nextThree = liftA3 (,,) (+ 1) (+ 2) (+ 3)
nextThree 5 == (6, 7, 8)
uncurry' f = f <$> fst <*> snd
-- or
uncurry' f = liftA2 f fst snd
uncurry' (+) (1, 2) == 3
The signature of liftM2 (==) is (Monad m, Eq a) => m a -> m a -> m Bool. So that means that if we call this function with id :: b -> b as argument, then it means that m a and b -> b are the same type.
The fact that m ~ (->) b holds is not a problem since (->) r is an instance of Monad, indeed in the GHC.Base source code we see:
-- | #since 2.01
instance Monad ((->) r) where
f >>= k = \ r -> k (f r) r
This only makes sense if m ~ (->) b. Here the arrow (->) is a type constructor, and (->) a b is the same as a -> b.
So it means that if we calculate the type of liftM2 (==) id, we derive the following:
liftM2 (==) :: m a -> m a -> m Bool
id :: (b -> b)
-------------------------------------------
m ~ (->) b, a ~ b
This thus means that the output type of liftM2 (==) id is liftM2 (==) id :: (Monad m, Eq a) => m a -> m Bool, but we need to "specialize" this with the knowledge we obtained: that m a is (->) b and a is the same type as b, so:
liftM2 (==) id :: (Monad m, Eq a) => m a -> m Bool
-> liftM2 (==) id :: (Monad m, Eq a) => (b -> a) -> (b -> Bool)
-> liftM2 (==) id :: Eq b => (b -> b) -> (b -> Bool)
-> liftM2 (==) id :: Eq b => (b -> b) -> b -> Bool
In short the function is still "monadic", although by using id, you have selected a specific monad, and thus the function is no longer applicable to all sorts of monads, only to the (->) r monad.
I have stumbled on this piece of code fold ((,) <$> sum <*> product) with type signature :: (Foldable t, Num a) => t a -> (a, a) and I got completely lost.
I know what it does, but I don't know how. So I tried to break it into little pieces in ghci:
λ: :t (<$>)
(<$>) :: Functor f => (a -> b) -> f a -> f b
λ: :t (,)
(,) :: a -> b -> (a, b)
λ: :t sum
sum :: (Foldable t, Num a) => t a -> a
Everything is okay, just basic stuff.
λ: :t (,) <$> sum
(,) <$> sum :: (Foldable t, Num a) => t a -> b -> (a, b)
And I am lost again...
I see that there is some magic happening that turns t a -> a into f a but how it is done is mystery to me. (sum is not even instance of Functor!)
I have always thought that f a is some kind of box f that contains a but it looks like the meaning is much deeper.
The functor f in your example is the so-called "reader functor", which is defined like this:
newtype Reader r = Reader (r -> a)
Of course, in Haskell, this is implemented natively for functions, so there is no wrapping or unwrapping at runtime.
The corresponding Functor and Applicative instances look like this:
instance Functor f where
fmap :: (a -> b) -> (r -> a)_-> (r -> b)
fmap f g = \x -> f (g x) -- or: fmap = (.)
instance Applicative f where
pure :: a -> (r -> a) -- or: a -> r -> a
pure x = \y -> x -- or: pure = const
(<*>) :: (r -> a -> b) -> (r -> a) -> (r -> b)
frab <*> fra = \r -> frab r (fra r)
In a way, the reader functor is a "box" too, like all the other functors, having a context r which produces a type a.
So let's look at (,) <$> sum:
:t (,) :: a -> b -> (a, b)
:t fmap :: (d -> e) -> (c -> d) -> (c -> e)
:t sum :: Foldable t, Num f => t f -> f
We can now specialize the d type to a ~ f, e to b -> (a, b) and c to t f. Now we get:
:t (<$>) -- spcialized for your case
:: Foldable t, Num f => (a -> (b -> (a, b))) -> (t f -> f) -> (t f -> (b -> (a, b)))
:: Foldable t, Num f => (f -> b -> (f, b)) -> (t f -> f) -> (t f -> b -> (f, b))
Applying the functions:
:t (,) <$> sum
:: Foldable t, Num f => (t f -> b -> (f, b))
Which is exactly what ghc says.
The short answer is that f ~ (->) (t a). To see why, just rearrange the type signature for sum slightly, using -> as a prefix operator instead of an infix operator.
sum :: (Foldable t, Num a) => (->) (t a) a
~~~~~~~~~~
f
In general, (->) r is a functor for any argument type r.
instance Functor ((->) r) where
fmap = (.)
It's easy to show that (.) is the only possible implementation for fmap here by plugging ((->) r) into the type of fmap for f:
fmap :: (a -> b) -> f a -> f b
:: (a -> b) -> ((->) r) a -> ((->) r) b
:: (a -> b) -> (r -> a) -> (r -> b)
This is the type signature for composition, and composition is the unique function that has this type signature.
Since Data.Functor defines <$> as an infix version of fmap, we have
(,) <$> sum == fmap (,) sum
== (.) (,) sum
From here, it is a relatively simple, though tedious, job of confirming that the resulting type is, indeed, (Foldable t, Num a) => t a -> b -> (a, b). We have
(b' -> c') -> (a' -> b') -> (a' -> c') -- composition
b' -> c' ~ a -> b -> (a,b) -- first argument (,)
a' -> b' ~ t n -> n -- second argument sum
----------------------------------------------------------------
a' ~ t n
b' ~ a ~ n
c' ~ a -> b -> (a,b)
----------------------------------------------------------------
a' -> c' ~ t a -> b -> (a,b)
Given a simple "language":
data Expr a where
ConstE :: a -> Expr a
FMapE :: (b -> a) -> Expr b -> Expr a
instance Functor Expr where
fmap = FMapE
interpret :: Expr a -> a
interpret (ConstE a) = a
interpret (FMapE f a) = f (interpret a)
From that I would like to extract a call graph, eg:
foo = fmap show . fmap (*2) $ ConstE 1
Should result in the graph Node 1 -> Node (*2) -> Node show. Ideally I'd like to store this in a Data.Graph.
What I've come up to this point is that it should be possible to use System.Mem.StableNames to identify individual nodes and store them in a HashMap (StableName (Expr a)) (Expr a).
toHashMap :: Expr a -> HashMap (StableName (Expr a)) (Expr a)
toHashMap n#ConstE = do
sn <- makeStableName n
return $ HashMap.singleton sn n
The problem is, that there seems to be no way to get through the FMapE nodes:
toHashMap n#(FMapE _ a) = do
snN <- makeStableName n
snA <- makeStableName a
-- recurse
hmA <- toHashMap a
-- combine
return $ HashMap.singleton snN n `HashMap.union` hmA
GHC will complain along the lines of this:
Couldn't match type ‘t’ with ‘b’
because type variable ‘b’ would escape its scope
This (rigid, skolem) type variable is bound by
a pattern with constructor
FMapE :: forall a b. (b -> a) -> Expr b -> Expr a,
in an equation for ‘toHashMap’
I can see that this won't match ... but I have no clue on how to make this work.
Edit
This probably boils down to writing a children function:
children :: Event a -> [Event a]
children (ConstE) = []
children (FMapE _ a) = [a] -- doesn't match ...
For the same reason I can't uniplate on this ...
You can get a postorder traversal, which is a tolopogical sort for a tree, of a type of kind * -> * from the Uniplate1 class I've described previously.
{-# LANGUAGE RankNTypes #-}
import Control.Applicative
import Control.Monad.Identity
class Uniplate1 f where
uniplate1 :: Applicative m => f a -> (forall b. f b -> m (f b)) -> m (f a)
descend1 :: (forall b. f b -> f b) -> f a -> f a
descend1 f x = runIdentity $ descendM1 (pure . f) x
descendM1 :: Applicative m => (forall b. f b -> m (f b)) -> f a -> m (f a)
descendM1 f a = uniplate1 a f
transform1 :: Uniplate1 f => (forall b. f b -> f b) -> f a -> f a
transform1 f = f . descend1 (transform1 f)
transform1 is a generic postorder tranformation. A generic postorder Monadic traversal of a Uniplate1 is
transformM1 :: (Uniplate1 f, Applicative m, Monad m) =>
(forall b. f b -> m (f b)) ->
f a -> m (f a)
transformM1 f = (>>= f) . descendM1 (transformM1 f)
We can write a Uniplate1 instance for Expr:
instance Uniplate1 Expr where
uniplate1 e p = case e of
FMapE f a -> FMapE f <$> p a
e -> pure e
We'll make a simple dump function for demonstration purposes and bypass to restore the data after a monadic effect.
dump :: Expr b -> IO ()
dump (ConstE _) = putStrLn "ConstE"
dump (FMapE _ _) = putStrLn "FMapE"
bypass :: Monad m => (a -> m ()) -> a -> m a
bypass f x = f x >> return x
We can traverse your example in topological order
> transformM1 (bypass dump) (fmap show . fmap (*2) $ ConstE 1)
ConstE
FMapE
FMapE