Endofunction as Monoid - haskell

I'm trying this (for learning purposes):
{-# LANGUAGE FlexibleInstances #-}
instance Monoid (a -> a) where
mempty = id
mappend f g = f . g
expecting id <> id to be equal to id . id
However, with (id <> id) 1 I receive this error:
Non type-variable argument in the constraint: Monoid (a -> a)
What should I change to run it?
It's just to understand monoids and Haskell typeclasses better, not for any practical usage.

This will need {-# OVERLAPPING #-} pragma since GHC.Base has an instance for Monoid (a -> b) when b is a Monoid:
{-# LANGUAGE FlexibleInstances #-}
import Data.Monoid (Monoid, mempty, mappend, (<>))
instance {-# OVERLAPPING #-} Monoid (a -> a) where
mempty = id
mappend f g = f . g
then, above instance will be invoked for a -> a, even if a is a Monoid:
\> (id <> id) 1
1
\> (id <> id) [1]
[1]
whereas with Monoid b => a -> b the instance from GHC.Base will be invoked:
\> ((:[]) <> (:[])) 1
[1,1]
Note that Data.Monoid provides an exact same instance as yours for a -> a but there the overlap is bypassed using newtype Endo a.

The Haskell Category class offers methods to work with categories whose objects are precisely the Haskell types of some kind. Specifically,
class Category c where
id :: c x x
(.) :: c y z -> c x y -> c x z
The names of the methods should look very familiar. Notably,
instance Category (->) where
id x = x
f . g = \x -> f (g x)
You probably know that monoids are semigroups with identities, expressed in Haskell using
class Monoid a where
mappend :: a -> a -> a
mempty :: a
But another mathematical perspective is that they're categories with exactly one object. If we have a monoid, we can easily turn it into a category:
-- We don't really need this extension, but
-- invoking it will make the code below more useful.
{-# LANGUAGE PolyKinds #-}
import Control.Category
import Data.Monoid
import Prelude hiding ((.), id)
newtype Mon m a b = Mon m
instance Monoid m => Category (Mon m) where
id = Mon mempty
Mon x . Mon y = Mon (x `mappend` y)
Going the other way is a little bit trickier. One way to do it is to choose a kind with exactly one type, and look at categories whose sole object is that type (prepare for yucky code, which you can skip if you like; the bit below is less scary). This shows that we can freely convert between a Category whose object is the type '() in the () kind and a Monoid. The arrows of the category become the elements of the monoid.
{-# LANGUAGE DataKinds, GADTs, PolyKinds #-}
data Cat (c :: () -> () -> *) where
Cat :: c '() '() -> Cat c
instance Category c => Monoid (Cat c) where
mempty = Cat id
Cat f `mappend` Cat g = Cat (f . g)
But this is yucky! Ew! And pinning things down so tightly doesn't usually accomplish anything from a practical perspective. But we can get the functionality without so much mess, by playing a little trick!
{-# LANGUAGE GADTs, PolyKinds #-}
import Control.Category
import Data.Monoid
import Prelude hiding ((.), id)
newtype Cat' (c :: k -> k -> *) (a :: k) (b :: k) = Cat' (c a b)
instance (a ~ b, Category c) => Monoid (Cat' c a b) where
mempty = Cat' id
Cat' f `mappend` Cat' g = Cat' (f . g)
Instead of confining ourselves to a Category that really only has one object, we simply confine ourselves to looking at one object at a time.
The existing Monoid instance for functions makes me sad. I think it would be much more natural to use a Monoid instance for functions based on their Category instance, using the Cat' approach:
instance a ~ b => Monoid (a -> b) where
mempty = id
mappend = (.)
Since there's already a Monoid instance, and overlapping instances are evil, we have to make do with a newtype. We could just use
newtype Morph a b = Morph {appMorph :: a -> b}
and then write
instance a ~ b => Monoid (Morph a b) where
mempty = Morph id
Morph f `mappend` Morph g = Morph (f . g)
and for some purposes maybe this is the way to go, but since we're using a newtype already we usually might as well drop the non-standard equality context and use Data.Monoid.Endo, which builds that equality into the type:
newtype Endo a = Endo {appEndo :: a -> a}
instance Monoid (Endo a) where
mempty = Endo id
Endo f `mappend` Endo g = Endo (f . g)

Related

Writing a generic functor instance across type constructors?

I'm learning basic type classes and have written my own implementation of functor for my type Test a (behaves just like Maybe):
data Test a = Test a | Emp
class FC c a where
t :: (a -> b) -> c a -> c b
instance FC Test a where
t f (Test a) = Test (f a)
t f (Emp) = Emp
instance FC Maybe a where
t f (Just a) = Just (f a)
t f (Nothing) = Nothing
Is it possible to implement something like:
instance FC c where
t f (c v) = c (f v)
Error:
Parse error in pattern: c
In other words, abstract away the type constructor, replace with c and v, therefore creating a general instance that can be applied to any value with a context?
As you've learned, c a is not a syntactically valid pattern. But reading your question instead as a feature proposal: How would that work? Not every Functor has a single-element constructor which can be mapped over according to your pattern. Some examples:
data Pair a = Pair a a -- more than one element
instance Functor Pair where
fmap f (Pair x y) = Pair (f x) (f y)
data Proxy a = Proxy -- no elements
instance Functor Proxy where
fmap f Proxy = Proxy
newtype Cont r a = Cont { runCont :: (a -> r) -> r } -- element appears in a double-negative position
instance Functor (Cont r) where
fmap f (Cont g) = Cont (g . (. f))
In any case, I don't think the idea of a "generic instance" really makes sense. The instance is where you put your type-specific code. (It has to go somewhere!)
If you want to exert less effort in writing Functor instances you can use GHC's DeriveFunctor extension.
{-# LANGUAGE DeriveFunctor #-}
data Pair a = Pair a a deriving Functor
data Proxy a = Proxy deriving Functor
newtype Cont r a = Cont { runCont :: (a -> r) -> r } deriving Functor
You can do something very generic using GHC.Generic. Here is an incomplete example for a generic FC class definition (this is exactly what the generic-deriving package does):
First some extensions and importing the generics machinery
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE DefaultSignatures #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE TypeOperators #-}
import GHC.Generics
Then we define a class which mirrors your FC but we only have instances for the generic types
class GFC c where
gt :: (a -> b) -> c a -> c b
-- Constructors without arguments (Empty)
instance GFC U1 where
gt _ U1 = U1
-- Constructors where the parameter appears (Test a)
instance GFC Par1 where
gt f (Par1 a) = Par1 (f a)
-- Sums (| in datatype definitions)
instance (GFC f, GFC g) => GFC (f :+: g) where
gt f (L1 a) = L1 (gt f a)
gt f (R1 a) = R1 (gt f a)
-- Meta information wrapper
instance GFC f => GFC (M1 i c f) where
gt f (M1 a) = M1 (gt f a)
-- ... the rest of the instances for the generic types here.
-- But these 4 instances are all that is needed for your `Test` type.
Then you can have a default implementation for FC based on the above "generic" FC:
class FC c where
t :: (a -> b) -> c a -> c b
default -- DefaultSignatures allows us to do this
t :: (Generic1 c, GFC (Rep1 c)) => (a -> b) -> c a -> c b
t f = to1 . gt f . from1
-- turn something with Generic1 into its generic representation,
-- use the generic `gt` and then turn it back into its actual
-- representation
data Test a = Test a | Empty
deriving (Generic1, Show)
instance FC Test
And it works:
GHCI> t (==0) (Test (1 :: Int))
Test False
As far as I know this is not possible, simply because there can be multiple constructors and it is unknown whether a generic constructor Foo can take any attribute as type.
Say for instance you have a type called:
data Foo a = Bar Int | Qux a
Now it means you cannot abstract away the constructor. As long as it is Qux, there is no problem, but Bar always expects an Int and thus will error. Since you here define an instance over any kind of c, there will be cases where this does not work. Note furthermore that the c in your instance declaration has nothing to do with the c in your definition of t. In other words: constructors can imply type constraints so you cannot simply factor them out.
A remark on your question is that you can generalize both you class defintion and instance:
class FC c where
t :: (a -> b) -> c a -> c b
instance FC Test where
t f (Test a) = Test (f a)
t f Emp = Emp
So you can remove the a in the class definition. This is not equivalent with your questions since here you say that it can work for any a. Whereas when you define a class FC c a you can decide for which as you want implement an instance.

Haskell combine multiple typeclass constraints

{-# LANGUAGE TypeFamilies #-}
import GHC.Prim
import qualified Data.Set as Set
class Functor' f where
type FConstraint f :: * -> Constraint
fmap' :: (FConstraint f a, FConstraint f b) => (a -> b) -> f a -> f b
instance Functor' Set.Set where
type FConstraint Set.Set = Ord Num --error here, won't let me put Num
fmap' = Set.map
I was wondering how I could make the above work. Now I know I could manually require two typeclasses, but I was hoping to be able to combine any arbitrary amount of them.
Now I know requiring Num does not make sense in this case, but this is purely an example.
You will need to define a typeclass (since typeclasses can be partially applied ) which reduces to the constraint you want through a superclass:
{-# LANGUAGE
PolyKinds, UndecidableInstances, TypeOperators
, MultiParamTypeClasses, ConstraintKinds, TypeFamilies
, FlexibleContexts, FlexibleInstances
#-}
class (f x, g x) => (&) f g (x :: k)
instance (f x, g x) => (&) f g x
Clearly (f & g) x holds iff f x and g x hold. The definition of FConstraint' should be obvious now:
class Functor' ...
instance Functor' Set.Set where
type FConstraint Set.Set = Ord & Num
fmap' f = Set.map ( (+1) . f ) -- (+1) to actually use the Num constraint
Looks like the only change I needed to make was not partially apply FConstraint:
{-# LANGUAGE TypeFamilies #-}
import GHC.Prim
import qualified Data.Set as Set
class Functor' f where
type FConstraint f a :: Constraint
fmap' :: (FConstraint f a, FConstraint f b) => (a -> b) -> f a -> f b
instance Functor' Set.Set where
type FConstraint Set.Set a = (Ord a, Num a)
fmap' f = Set.map ((+ 1) . f)
foo = fmap (+ 1) $ Set.fromList [1, 2, 3]
Unfortunately this does not allow me to use a concrete type as far as I can tell, but I suppose that wouldn't even match with Functor on a kind level anyway (Functor has kind * -> * but a list of concrete values such as String has kind *).

Is it possible to encode a generic "lift" function in Haskell?

I'm not the biggest fan of varargs, but I always thought both the applicative (f <$> x <*> y) and idiom ([i| f x y |]) styles have too many symbols. I usually prefer going the liftA2 f x y way, but I, too, think that A2 is a little ugly. From this question, I've learned it is possible to implement vararg functions in Haskell. This way, is it possible to use the same principle in order implement a lift function, such that:
lift f a b == pure f <*> a <*> b
I've tried replacing the + by <*> on the quoted code:
class Lift r where
lift :: a -> r
instance Lift a where
lift = id
instance (Lift r) => Lift (a -> r) where
lift x y = lift (x <*> y)
But I couldn't manage to get the types right...
Notice that you can chain any number of <*>, to get a function of the form
f (a0 -> .. -> an) -> (f a0 -> .. -> f an)
If we have the type a0 -> .. -> an and f a0 -> .. -> f an, we can compute f from this. We can encode this relation, and the most general type, as follows
class Lift a f b | a b -> f where
lift' :: f a -> b
As you may expect, the "recursive case" instance will simply apply <*> once, then recurse:
instance (a ~ a', f' ~ f, Lift as f rs, Applicative f)
=> Lift (a -> as) f (f' a' -> rs) where
lift' f a = lift' $ f <*> a
The base case is when there is no more function. Since you can't actually assert "a is not a function type", this relies on overlapping instances:
instance (f a ~ b) => Lift a f b where
lift' = id
Because of GHCs instance selection rules, the recursive case will always be selected, if possible.
Then the function you want is lift' . pure :
lift :: (Lift a f b, Applicative f) => a -> b
lift x = lift' (pure x)
This is where the functional dependency on Lift becomes very important. Since f is mentioned only in the context, this function would be ill-typed unless we can determine what f is knowing only a and b (which do appear in the right hand side of =>).
This requires several extensions:
{-# LANGUAGE
OverlappingInstances
, MultiParamTypeClasses
, UndecidableInstances
, FunctionalDependencies
, ScopedTypeVariables
, TypeFamilies
, FlexibleInstances
#-}
and, as usual with variadic functions in Haskell, normally the only way to select an instance is to give an explicit type signature.
lift (\x y z -> x * y + z) readLn readLn readLn :: IO Int
The way I have written it, GHC will happily accept lift which is polymorphic in the arguments to f (but not f itself).
lift (+) [1..5] [3..5] :: (Enum a, Num a) => [a]
Sometimes the context is sufficient to infer the correct type. Note that the argument type is again polymorphic.
main = lift (\x y z -> x * y + z) readLn readLn readLn >>= print
As of GHC >= 7.10, OverlappingInstances has been deprecated and the compiler will issue a warning. It will likely be removed in some later version. This can be fixed by removing OverlappingInstances from the {-# LANGUAGE .. #-} pragma and changing the 2nd instance to
instance {-# OVERLAPS #-} (f a ~ b) => Lift a f b where
I assume you would prefer to use lift without type annotations. In this case there are basically two options:
First, if we use OverlappingInstances, polymorphic functions need annotations:
{-# LANGUAGE
OverlappingInstances,
MultiParamTypeClasses,
UndecidableInstances,
FunctionalDependencies,
FlexibleInstances,
TypeFamilies
#-}
import Control.Applicative
class Applicative f => ApN f a b | a b -> f where
apN :: f a -> b
instance (Applicative f, b ~ f a) => ApN f a b where
apN = id
instance (Applicative f, ApN f a' b', b ~ (f a -> b')) => ApN f (a -> a') b where
apN f fa = apN (f <*> fa)
lift :: ApN f a b => a -> b
lift a = apN (pure a)
-- Now we can't write "lift (+) (Just 0) Nothing"
-- We must annotate as follows:
-- lift ((+) :: Int -> Int -> Int) (Just 0) Nothing
-- Monomorphic functions work fine though:
-- lift (||) (Just True) (Just True) --> results in "Just True"
Second, if we instead use IncoherentInstances, lift will work without annotations even on polymorphic functions. However, some complicated stuff still won't check out, for example (lift . lift) (+) (Just (Just 0)) Nothing.
{-# LANGUAGE
IncoherentInstances, MultiParamTypeClasses,
UndecidableInstances,ScopedTypeVariables,
AllowAmbiguousTypes, FlexibleInstances, TypeFamilies
#-}
import Control.Applicative
class Applicative f => ApN f a b where
apN :: f a -> b
instance (Applicative f, b ~ f a) => ApN f a b where
apN = id
instance (Applicative f, ApN f a' b', b ~ (f a -> b')) => ApN f (a -> a') b where
apN f fa = apN (f <*> fa)
lift :: forall f a b. ApN f a b => a -> b
lift a = (apN :: f a -> b) (pure a)
-- now "lift (+) (Just 0) (Just 10)" works out of the box
I presented two solutions instead of just the one with IncoherentInstances because IncoherentInstances is a rather crude extension that should be avoided if possible. It's probably fine here, but I thought it worthwhile to provide an alternative solution, anyway.
In both cases I use the same trick to help inference and reduce annotations: I try to move information from the instance heads to the instance constraints. So instead of
instance (Applicative f) => ApN f a (f a) where
apN = id
I write
instance (Applicative f, b ~ f a) => ApN f a b where
apN = id
Also, in the other instance I use a plain b parameter in the instance head and add b ~ (f a ~ b') to the constraints.
The reason for doing this is that GHC first checks if there is a matching instance head, and it tries to resolve the constraints only after there is a successful match. We want to place the least amount of burden on the instance head, and let the constraint solver sort things out (because it's more flexible, can delay making judgements and can use constraints from other parts of the program).

List of Functors

This might apply for any type class, but lets do it for Functors as I know them better. I wan't to construct this list.
l = [Just 1, [1,2,3], Nothing, Right 4]
and then
map (fmap (+1)) l
to get
[Just 2, [2,3,4], Nothing, Right 5]
I know they are all Functors that contain Ints so it might be possible. How can I do this?
Edit
This is turning out to be messier than it would seem. In Java or C# you'd declare the IFunctor interface and then just write
List<IFunctor> l = new List<IFunctor> () {
new Just (1),
new List<Int>() {1,2,3},
new Nothing<Int>(),
new Right (5)
}
assuming Maybe, List and Either implement the IFunctor. Naturally Just and Nothing extend Maybe and Right and Left extend Either. Not satisfied with this problem being easier to resolve on these languages!!!
There should cleaner way in Haskell :(
In Haskell, downcasting is not allowed. You can use AnyFunctor, but the trouble with that is there is no longer any way to get back to a functor that you know. When you have an AnyFunctor a, all you know is that you have an f a for some f, so all you can do is fmap (getting you another AnyFunctor). Thus, AnyFunctor a is in fact equivalent to ().
You can add structure to AnyFunctor to make it more useful, and we'll see a bit of that later on.
Functor Coproducts
But first, I'll share the way that I would probably end up doing this in a real program: by using functor combinators.
{-# LANGUAGE TypeOperators #-}
infixl 1 :+: -- declare this to be a left-associative operator
data (f :+: g) a = FLeft (f a) | FRight (g a)
instance (Functor f, Functor g) => Functor (f :+: g) where
-- left as an exercise
As the data type reads, f :+: g is a functor whose values can be either f a or g a.
Then you can use, for example:
l :: [ (Maybe :+: []) Int ]
l = [ FLeft (Just 1), FRight [2,3,4], FLeft Nothing ]
And you can observe by pattern matching:
getMaybe :: (Maybe :+: g) a -> Maybe a
getMaybe (FLeft v) = v
getMaybe (FRight _) = Nothing
It gets ugly as you add more functors:
l :: [ (Maybe :+: [] :+: Either Int) Int ]
l = [ FLeft (FLeft Nothing), FRight (Right 42) ]
-- Remember that we declared :+: left-associative.
But I recommend it as long as you can handle the ugliness, because it tracks the list of possible functors in the type, which is an advantage. (Perhaps you eventually need more structure beyond what Functor can provide; as long as you can provide it for (:+:), you're in good territory.)
You can make the terms a bit cleaner by creating an explicit union, as Ganesh recommends:
data MyFunctors a
= FMaybe (Maybe a)
| FList [a]
| FEitherInt (Either Int a)
| ...
But you pay by having to re-implement Functor for it ({-# LANGUAGE DeriveFunctor #-} can help). I prefer to put up with the ugliness, and work at a high enough level of abstraction where it doesn't get too ugly (i.e. once you start writing FLeft (FLeft ...) it's time to refactor & generalize).
Coproduct can be found in the comonad-transformers package if you don't want to implement it yourself (it's good exercise though). Other common functor combinators are in the Data.Functor. namespace in the transformers package.
Existentials with Downcasting
AnyFunctor can also be extended to allow downcasting. Downcasting must be explicitly enabled by adding the Typeable class to whatever you intend to downcast. Every concrete type is an instance of Typeable; type constructors are instances of Typeable1 (1 argument); etc. But it doesn't come for free on type variables, so you need to add class constraints. So the AnyFunctor solution becomes:
{-# LANGUAGE GADTs #-}
import Data.Typeable
data AnyFunctor a where
AnyFunctor :: (Functor f, Typeable1 f) => f a -> AnyFunctor a
instance Functor AnyFunctor where
fmap f (AnyFunctor v) = AnyFunctor (fmap f v)
Which allows downcasting:
downcast :: (Typeable1 f, Typeable a) => AnyFunctor a -> Maybe (f a)
downcast (AnyFunctor f) = cast f
This solution is actually cleaner than I had expected to be, and may be worth pursuing.
One approach is to use existentials:
{-# LANGUAGE GADTs #-}
data AnyFunctor v where
AnyFunctor :: Functor f => f v -> AnyFunctor v
instance Functor AnyFunctor where
fmap f (AnyFunctor fv) = AnyFunctor (fmap f fv)
The input list you ask for in your question isn't possible as it stands because it's not correctly typed, so some wrapping like AnyFunctor is likely to be necessary however you approach it.
You can make the input list by wrapping each value in the AnyFunctor data constructor:
[AnyFunctor (Just 1), AnyFunctor [1,2,3],
AnyFunctor Nothing, AnyFunctor (Right 4)]
Note that when you use fmap (+1) it's a good idea to use an explicit type signature for the 1 to avoid any problems with numeric overloading, e.g. fmap (+(1::Integer)).
The difficulty with AnyFunctor v as it stands is that you can't actually do much with it - you can't even look at the results because it isn't an instance of Show, let alone extract a value for future use.
It's a little tricky to make it into an instance of Show. If we add a Show (f v) constraint to the AnyFunctor data constructor, then the Functor instance stops working because there's no guarantee it'll produce an instance of Show itself. Instead we need to use a sort of "higher-order" typeclass Show1, as discussed in this answer:
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE GADTs #-}
data AnyFunctor v where
AnyFunctor :: (Show1 f, Functor f) => f v -> AnyFunctor v
instance Functor AnyFunctor where
fmap f (AnyFunctor fv) = AnyFunctor (fmap f fv)
data ShowDict a where
ShowDict :: Show a => ShowDict a
class Show1 a where
show1Dict :: ShowDict b -> ShowDict (a b)
instance Show v => Show (AnyFunctor v) where
show (AnyFunctor (v :: f v)) =
case show1Dict ShowDict :: ShowDict (f v) of
ShowDict -> "AnyFunctor (" ++ show v ++ ")"
instance Show1 [] where
show1Dict ShowDict = ShowDict
instance Show1 Maybe where
show1Dict ShowDict = ShowDict
instance Show a => Show1 (Either a) where
show1Dict ShowDict = ShowDict
In ghci this gives the following (I've broken the lines for readability):
*Main> map (fmap (+1)) [AnyFunctor (Just 1), AnyFunctor [1,2,3],
AnyFunctor Nothing, AnyFunctor (Right 4)]
[AnyFunctor (Just 2),AnyFunctor ([2,3,4]),
AnyFunctor (Nothing),AnyFunctor (Right 5)]
The basic idea is to express the idea that a type constructor like Nothing, [] or Either a "preserves" the Show constraint, using the Show1 class to say that Show (f v) is available whenever Show v is available.
The same trick applies with other typeclasses. For example #luqui's answer shows how you can extract values using the Typeable class, which already has a built-in Typeable1 variant. Each type class that you add limits the things that you can put into AnyFunctor, but also means you can do more things with it.
One option would be to create a specific data type for your use case, with the additional advantage of having proper names for things.
Another would be to create a specialized * -> * tuples as:
newtype FTuple4 fa fb fc fd r = FTuple4 (fa r, fb r, fc r, fd r)
deriving (Eq, Ord, Show)
So the tuple is homogeneous in values, but heterogeneous in functors.
Then you can define
instance (Functor fa, Functor fb, Functor fc, Functor fd) =>
Functor (FTuple4 fa fb fc fd) where
fmap f (FTuple4 (a, b, c, d)) =
FTuple4 (fmap f a, fmap f b, fmap f c, fmap f d)
and
main = let ft = FTuple4 (Just 1,
[1,2,3],
Nothing,
Right 4 :: Either String Int)
in print $ fmap (+ 1) ft
With this approach, you can pattern match on the result easily, without losing information about the types of the individual elements, their order etc. And, you can have similar instances for Foldable, Traversable, Applicative etc.
Also you don't need to implement the Functor instance yourself, you can use GHC's deriving extensions, so all you need to write to get all the instances is is just
{-# LANGUAGE DeriveFunctor, DeriveFoldable, DeriveTraversable #-}
import Data.Foldable
import Data.Traversable
newtype FTuple4 fa fb fc fd r = FTuple4 (fa r, fb r, fc r, fd r)
deriving (Eq, Ord, Show, Functor, Foldable, Traversable)
And even this can be further automated for arbitrary length using Template Haskell.
The advantage of this approach is mainly in the fact that it just wraps ordinary tuples, so you can seamlessly switch between (,,,) and FTuple4, if you need.
Another alternative, without having your own data type, would be to use nested functor products, since what you're describing is just a product of 4 functors.
import Data.Functor.Product
main = let ft = Pair (Just 1)
(Pair [1,2,3]
(Pair Nothing
(Right 4 :: Either String Int)
))
(Pair a (Pair b (Pair c d))) = fmap (+ 1) ft
in print (a, b, c, d)
This is somewhat verbose, but you can do much better by creating your own functor product using type operators:
{-# LANGUAGE TypeOperators, DeriveFunctor #-}
data (f :*: g) a = f a :*: g a
deriving (Eq, Ord, Show, Functor)
infixl 1 :*:
main = let a :*: b :*: c :*: d = fmap (+ 1) $ Just 1 :*:
[1,2,3] :*:
Nothing :*:
(Right 4 :: Either String Int)
in print (a, b, c, d)
This gets probably as terse and universal as possible.

Making (a, a) a Functor

How can I make (a, a) a Functor without resorting to a newtype?
Basically I want it to work like this:
instance Functor (a, a) where
fmap f (x, y) = (f x, f y)
But of course that's not a legal way to express it:
Kind mis-match
The first argument of `Functor' should have kind `* -> *',
but `(a, a)' has kind `*'
In the instance declaration for `Functor (a, a)'
What I really want is a type-level function like this: \a -> (a, a) (invalid syntax). So a type alias, perhaps?
type V2 a = (a, a)
instance Functor V2 where
fmap f (x, y) = (f x, f y)
I would think this would work, but it doesn't. First I get this complaint:
Illegal instance declaration for `Functor V2'
(All instance types must be of the form (T t1 ... tn)
where T is not a synonym.
Use -XTypeSynonymInstances if you want to disable this.)
In the instance declaration for `Functor V2'
If I follow the advice and add the TypeSynonymInstances extension, I get a new error:
Type synonym `V2' should have 1 argument, but has been given 0
In the instance declaration for `Functor V2'
Well, duh, that's the point! V2 has kind * -> * which is what is required of a Functor instance. Well, ok, I can use a newtype like this:
newtype V2 a = V2 (a, a)
instance Functor V2 where
fmap f (V2 (x, y)) = V2 (f x, f y)
But now I've got to sprinkle V2s liberally throughout my code instead of just being able to deal with simple tuples, which kind of defeats the point of making it a Functor; at that point I might as well make my own function vmap :: (a -> b) -> (a, a) -> (b, b).
So is there any way to do this nicely, i.e. without a newtype?
As others have stated, there's no way to do this without resorting to newtypes or data declarations. However, have you looked at Control.Arrow? Many of those functions are very useful with tuples, for example:
vmap :: (a -> b) -> (a,a) -> (b,b)
vmap f = f *** f
You can declare
instance Functor ((,) a) where
...
However that doesn't constrain the first element of your pair, and fmap would only act on the second element.
The issue is that a tuple doesn't enforce a relationship between the types of the two elements.
If you don't want a newtype decorator you can make your own fresh type:
data Pair a = P a a
instance Functor Pair where
...
which will be easier to work with than a newtype around a tuple.
With singletons you can define a Functor type class for defunctionalized symbols (Type ~> Type instead of Type -> Type)
{-# Language ExplicitNamespaces, TypeApplications, TypeOperators, KindSignatures, ScopedTypeVariables, DataKinds, TypeInType, TypeFamilies, AllowAmbiguousTypes, InstanceSigs #-}
import Data.Kind (Type)
import Data.Singletons (type (~>), Apply)
class Functor' (f :: Type ~> Type) where
fmap' :: (a -> a') -> (Apply f a -> Apply f a')
data Dup :: Type ~> Type
type instance Dup `Apply` a = (a, a)
instance Functor' Dup where
fmap' :: (a -> a') -> ((a, a) -> (a', a'))
fmap' f (a1, a2) = (f a1, f a2)
This gives you a Prelude.Functor instance automatically
newtype f $ a = App (Apply f a)
instance Functor' f => Functor (($) f) where
fmap :: (a -> a') -> (f $ a -> f $ a')
fmap f (App fa) = App (fmap' #f f fa)

Resources