{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DeriveTraversable #-}
{-# LANGUAGE DerivingVia #-}
{-# LANGUAGE DeriveTraversable #-}
{-# LANGUAGE LinearTypes #-}
{-# LANGUAGE GADTSyntax #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE Trustworthy #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE StandaloneKindSignatures #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}

-- | The definitions of 'Generic', 'Generic1', 'MP1', 'unMP1', and ':.:'.
-- Users should import 'Generics.Linear' instead.
module Generics.Linear.Class
  ( Generic (..)
  , Generic1 (..)
  , (:.:)(..)
  , MP1 (..)
  , unMP1
  , module GHC.Generics
  ) where
import Control.Applicative
import Data.Foldable (Foldable (..))
import Data.Functor.Classes
import Data.Functor.Contravariant
import GHC.Generics hiding (Generic (..), Generic1 (..), (:.:)(..), Rec1 (..))
import qualified GHC.Generics as G
import Control.Monad (MonadPlus (..))
import GHC.Types (Multiplicity (..))
import Data.Kind (Constraint, Type)
import Data.Data (Data)
import qualified Data.Data as D
import Data.Semigroup (Semigroup (..))
import Data.Typeable (Typeable, gcast1)

-- | @Generic@ is exactly the same as @"GHC.Generics".'Generic'@
-- except that `to` and `from` are multiplicity polymorphic. This
-- means they will work equally well in traditional Haskell code
-- and in linearly typed code.
type Generic :: Type -> Constraint
class Generic a where
  type family Rep a :: Type -> Type

  to :: forall p m. Rep a p %m-> a
  from :: forall p m. a %m-> Rep a p

-- | @Generic1@ is similar to @"GHC.Generics".'Generic1'@, but has a few
-- differences.
--
-- == Multiplicity polymorphism
--
-- As with 'Generic', the @to1@ and @from1@ methods are
-- multiplicity polymorphic.
--
-- == Differences in 'Rep1' representation
--
-- === 'G.Rec1' is not used
--
-- Given a type like
--
-- @
-- newtype Foo a = Foo (Maybe a)
-- @
--
-- where a single type constructor (here @Maybe@) is applied to the
-- parameter, "GHC.Generics" represents the field as @'G.Rec1' Maybe@.
-- We instead represent it using @Par1 :.: Maybe@. It is expected
-- that very few real-life uses of "GHC.Generics" will break as a
-- result, and this simplification means that users don't have to
-- write 'G.Rec1' instances for their generic-deriving classes.
--
-- === Compositions associate in the opposite order
--
-- Given a type like
--
-- @
-- newtype Bar a = Bar (Maybe [Either e a])
-- @
--
-- where multiple type constructors are layered around the parameter,
-- "GHC.Generics@ represents the field as
--
-- @
-- Maybe 'G.:.:' ([] 'G.:.:' 'G.Rec1' (Either e))
-- @
--
-- We instead represent it as
--
-- @
-- (('Par1' ':.:' Maybe) ':.:' []) ':.:' Either e
-- @
--
-- Doing it this way prevents `to1` and `from1` from having to 'fmap' newtype
-- constructors through the composed types, which can be a considerable
-- performance improvement and enables multiplicity polymorphism.
--
-- In most cases, modifying generic-deriving classes to accommodate this change
-- is simple: just swap which side of the composition is treated as a generic
-- representation and which as a base type. In a few cases, more restructuring
-- will be needed, which will require using different generic-deriving classes
-- than for "GHC.Generics".
--
-- == Difference in specificity
--
-- Users of type application will need to be aware that the kind parameter for
-- 'Generic1' is marked as inferred, whereas for @"GHC.Generics".'Generic1'@ it
-- is marked as specified. So you should use, for example, @to1 \@Maybe@ rather
-- than @to1 \@_ \@Maybe@.

type Generic1 :: forall {k}. (k -> Type) -> Constraint
class Generic1 (f :: k -> Type) where
  type family Rep1 f :: k -> Type

  to1 :: forall p m. Rep1 f p %m-> f p
  from1 :: forall p m. f p %m-> Rep1 f p

infixl 7 :.:

-- | The composition operator for types. We use our own here because for many
-- classes, it's possible to share generic deriving classes between
-- "GHC.Generics" and "Generics.Linear" by just instantiating them for both
-- composition operators (and 'MP1').
type (:.:) :: forall k2 k1. (k2 -> Type) -> (k1 -> k2) -> k1 -> Type
-- See Note: kind specificity
newtype (f :.: g) x = Comp1 { forall k2 k1 (f :: k2 -> *) (g :: k1 -> k2) (x :: k1).
(:.:) f g x -> f (g x)
unComp1 :: f (g x) }
  deriving stock ( (:.:) f g x -> (:.:) f g x -> Bool
((:.:) f g x -> (:.:) f g x -> Bool)
-> ((:.:) f g x -> (:.:) f g x -> Bool) -> Eq ((:.:) f g x)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall k2 (f :: k2 -> *) k1 (g :: k1 -> k2) (x :: k1).
Eq (f (g x)) =>
(:.:) f g x -> (:.:) f g x -> Bool
/= :: (:.:) f g x -> (:.:) f g x -> Bool
$c/= :: forall k2 (f :: k2 -> *) k1 (g :: k1 -> k2) (x :: k1).
Eq (f (g x)) =>
(:.:) f g x -> (:.:) f g x -> Bool
== :: (:.:) f g x -> (:.:) f g x -> Bool
$c== :: forall k2 (f :: k2 -> *) k1 (g :: k1 -> k2) (x :: k1).
Eq (f (g x)) =>
(:.:) f g x -> (:.:) f g x -> Bool
Eq, Eq ((:.:) f g x)
Eq ((:.:) f g x)
-> ((:.:) f g x -> (:.:) f g x -> Ordering)
-> ((:.:) f g x -> (:.:) f g x -> Bool)
-> ((:.:) f g x -> (:.:) f g x -> Bool)
-> ((:.:) f g x -> (:.:) f g x -> Bool)
-> ((:.:) f g x -> (:.:) f g x -> Bool)
-> ((:.:) f g x -> (:.:) f g x -> (:.:) f g x)
-> ((:.:) f g x -> (:.:) f g x -> (:.:) f g x)
-> Ord ((:.:) f g x)
(:.:) f g x -> (:.:) f g x -> Bool
(:.:) f g x -> (:.:) f g x -> Ordering
(:.:) f g x -> (:.:) f g x -> (:.:) f g x
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall {k2} {f :: k2 -> *} {k1} {g :: k1 -> k2} {x :: k1}.
Ord (f (g x)) =>
Eq ((:.:) f g x)
forall k2 (f :: k2 -> *) k1 (g :: k1 -> k2) (x :: k1).
Ord (f (g x)) =>
(:.:) f g x -> (:.:) f g x -> Bool
forall k2 (f :: k2 -> *) k1 (g :: k1 -> k2) (x :: k1).
Ord (f (g x)) =>
(:.:) f g x -> (:.:) f g x -> Ordering
forall k2 (f :: k2 -> *) k1 (g :: k1 -> k2) (x :: k1).
Ord (f (g x)) =>
(:.:) f g x -> (:.:) f g x -> (:.:) f g x
min :: (:.:) f g x -> (:.:) f g x -> (:.:) f g x
$cmin :: forall k2 (f :: k2 -> *) k1 (g :: k1 -> k2) (x :: k1).
Ord (f (g x)) =>
(:.:) f g x -> (:.:) f g x -> (:.:) f g x
max :: (:.:) f g x -> (:.:) f g x -> (:.:) f g x
$cmax :: forall k2 (f :: k2 -> *) k1 (g :: k1 -> k2) (x :: k1).
Ord (f (g x)) =>
(:.:) f g x -> (:.:) f g x -> (:.:) f g x
>= :: (:.:) f g x -> (:.:) f g x -> Bool
$c>= :: forall k2 (f :: k2 -> *) k1 (g :: k1 -> k2) (x :: k1).
Ord (f (g x)) =>
(:.:) f g x -> (:.:) f g x -> Bool
> :: (:.:) f g x -> (:.:) f g x -> Bool
$c> :: forall k2 (f :: k2 -> *) k1 (g :: k1 -> k2) (x :: k1).
Ord (f (g x)) =>
(:.:) f g x -> (:.:) f g x -> Bool
<= :: (:.:) f g x -> (:.:) f g x -> Bool
$c<= :: forall k2 (f :: k2 -> *) k1 (g :: k1 -> k2) (x :: k1).
Ord (f (g x)) =>
(:.:) f g x -> (:.:) f g x -> Bool
< :: (:.:) f g x -> (:.:) f g x -> Bool
$c< :: forall k2 (f :: k2 -> *) k1 (g :: k1 -> k2) (x :: k1).
Ord (f (g x)) =>
(:.:) f g x -> (:.:) f g x -> Bool
compare :: (:.:) f g x -> (:.:) f g x -> Ordering
$ccompare :: forall k2 (f :: k2 -> *) k1 (g :: k1 -> k2) (x :: k1).
Ord (f (g x)) =>
(:.:) f g x -> (:.:) f g x -> Ordering
Ord, Int -> (:.:) f g x -> ShowS
[(:.:) f g x] -> ShowS
(:.:) f g x -> String
(Int -> (:.:) f g x -> ShowS)
-> ((:.:) f g x -> String)
-> ([(:.:) f g x] -> ShowS)
-> Show ((:.:) f g x)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall k2 (f :: k2 -> *) k1 (g :: k1 -> k2) (x :: k1).
Show (f (g x)) =>
Int -> (:.:) f g x -> ShowS
forall k2 (f :: k2 -> *) k1 (g :: k1 -> k2) (x :: k1).
Show (f (g x)) =>
[(:.:) f g x] -> ShowS
forall k2 (f :: k2 -> *) k1 (g :: k1 -> k2) (x :: k1).
Show (f (g x)) =>
(:.:) f g x -> String
showList :: [(:.:) f g x] -> ShowS
$cshowList :: forall k2 (f :: k2 -> *) k1 (g :: k1 -> k2) (x :: k1).
Show (f (g x)) =>
[(:.:) f g x] -> ShowS
show :: (:.:) f g x -> String
$cshow :: forall k2 (f :: k2 -> *) k1 (g :: k1 -> k2) (x :: k1).
Show (f (g x)) =>
(:.:) f g x -> String
showsPrec :: Int -> (:.:) f g x -> ShowS
$cshowsPrec :: forall k2 (f :: k2 -> *) k1 (g :: k1 -> k2) (x :: k1).
Show (f (g x)) =>
Int -> (:.:) f g x -> ShowS
Show, ReadPrec [(:.:) f g x]
ReadPrec ((:.:) f g x)
Int -> ReadS ((:.:) f g x)
ReadS [(:.:) f g x]
(Int -> ReadS ((:.:) f g x))
-> ReadS [(:.:) f g x]
-> ReadPrec ((:.:) f g x)
-> ReadPrec [(:.:) f g x]
-> Read ((:.:) f g x)
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
forall k2 (f :: k2 -> *) k1 (g :: k1 -> k2) (x :: k1).
Read (f (g x)) =>
ReadPrec [(:.:) f g x]
forall k2 (f :: k2 -> *) k1 (g :: k1 -> k2) (x :: k1).
Read (f (g x)) =>
ReadPrec ((:.:) f g x)
forall k2 (f :: k2 -> *) k1 (g :: k1 -> k2) (x :: k1).
Read (f (g x)) =>
Int -> ReadS ((:.:) f g x)
forall k2 (f :: k2 -> *) k1 (g :: k1 -> k2) (x :: k1).
Read (f (g x)) =>
ReadS [(:.:) f g x]
readListPrec :: ReadPrec [(:.:) f g x]
$creadListPrec :: forall k2 (f :: k2 -> *) k1 (g :: k1 -> k2) (x :: k1).
Read (f (g x)) =>
ReadPrec [(:.:) f g x]
readPrec :: ReadPrec ((:.:) f g x)
$creadPrec :: forall k2 (f :: k2 -> *) k1 (g :: k1 -> k2) (x :: k1).
Read (f (g x)) =>
ReadPrec ((:.:) f g x)
readList :: ReadS [(:.:) f g x]
$creadList :: forall k2 (f :: k2 -> *) k1 (g :: k1 -> k2) (x :: k1).
Read (f (g x)) =>
ReadS [(:.:) f g x]
readsPrec :: Int -> ReadS ((:.:) f g x)
$creadsPrec :: forall k2 (f :: k2 -> *) k1 (g :: k1 -> k2) (x :: k1).
Read (f (g x)) =>
Int -> ReadS ((:.:) f g x)
Read
                 , (forall x. (:.:) f g x -> Rep ((:.:) f g x) x)
-> (forall x. Rep ((:.:) f g x) x -> (:.:) f g x)
-> Generic ((:.:) f g x)
forall x. Rep ((:.:) f g x) x -> (:.:) f g x
forall x. (:.:) f g x -> Rep ((:.:) f g x) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall k2 (f :: k2 -> *) k1 (g :: k1 -> k2) (x :: k1) x.
Rep ((:.:) f g x) x -> (:.:) f g x
forall k2 (f :: k2 -> *) k1 (g :: k1 -> k2) (x :: k1) x.
(:.:) f g x -> Rep ((:.:) f g x) x
$cto :: forall k2 (f :: k2 -> *) k1 (g :: k1 -> k2) (x :: k1) x.
Rep ((:.:) f g x) x -> (:.:) f g x
$cfrom :: forall k2 (f :: k2 -> *) k1 (g :: k1 -> k2) (x :: k1) x.
(:.:) f g x -> Rep ((:.:) f g x) x
G.Generic, (forall (a :: k). (:.:) f g a -> Rep1 (f :.: g) a)
-> (forall (a :: k). Rep1 (f :.: g) a -> (:.:) f g a)
-> Generic1 (f :.: g)
forall (a :: k). Rep1 (f :.: g) a -> (:.:) f g a
forall (a :: k). (:.:) f g a -> Rep1 (f :.: g) a
forall k (f :: k -> *).
(forall (a :: k). f a -> Rep1 f a)
-> (forall (a :: k). Rep1 f a -> f a) -> Generic1 f
forall (f :: * -> *) k (g :: k -> *) (a :: k).
Functor f =>
Rep1 (f :.: g) a -> (:.:) f g a
forall (f :: * -> *) k (g :: k -> *) (a :: k).
Functor f =>
(:.:) f g a -> Rep1 (f :.: g) a
$cto1 :: forall (f :: * -> *) k (g :: k -> *) (a :: k).
Functor f =>
Rep1 (f :.: g) a -> (:.:) f g a
$cfrom1 :: forall (f :: * -> *) k (g :: k -> *) (a :: k).
Functor f =>
(:.:) f g a -> Rep1 (f :.: g) a
G.Generic1, Typeable ((:.:) f g x)
Typeable ((:.:) f g x)
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> (:.:) f g x -> c ((:.:) f g x))
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c ((:.:) f g x))
-> ((:.:) f g x -> Constr)
-> ((:.:) f g x -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c ((:.:) f g x)))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e))
    -> Maybe (c ((:.:) f g x)))
-> ((forall b. Data b => b -> b) -> (:.:) f g x -> (:.:) f g x)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> (:.:) f g x -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> (:.:) f g x -> r)
-> (forall u. (forall d. Data d => d -> u) -> (:.:) f g x -> [u])
-> (forall u.
    Int -> (forall d. Data d => d -> u) -> (:.:) f g x -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> (:.:) f g x -> m ((:.:) f g x))
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> (:.:) f g x -> m ((:.:) f g x))
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> (:.:) f g x -> m ((:.:) f g x))
-> Data ((:.:) f g x)
(:.:) f g x -> DataType
(:.:) f g x -> Constr
(forall b. Data b => b -> b) -> (:.:) f g x -> (:.:) f g x
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> (:.:) f g x -> u
forall u. (forall d. Data d => d -> u) -> (:.:) f g x -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> (:.:) f g x -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> (:.:) f g x -> r
forall {k2} {f :: k2 -> *} {k1} {g :: k1 -> k2} {x :: k1}.
(Typeable x, Typeable f, Typeable g, Typeable k2, Typeable k1,
 Data (f (g x))) =>
Typeable ((:.:) f g x)
forall k2 (f :: k2 -> *) k1 (g :: k1 -> k2) (x :: k1).
(Typeable x, Typeable f, Typeable g, Typeable k2, Typeable k1,
 Data (f (g x))) =>
(:.:) f g x -> DataType
forall k2 (f :: k2 -> *) k1 (g :: k1 -> k2) (x :: k1).
(Typeable x, Typeable f, Typeable g, Typeable k2, Typeable k1,
 Data (f (g x))) =>
(:.:) f g x -> Constr
forall k2 (f :: k2 -> *) k1 (g :: k1 -> k2) (x :: k1).
(Typeable x, Typeable f, Typeable g, Typeable k2, Typeable k1,
 Data (f (g x))) =>
(forall b. Data b => b -> b) -> (:.:) f g x -> (:.:) f g x
forall k2 (f :: k2 -> *) k1 (g :: k1 -> k2) (x :: k1) u.
(Typeable x, Typeable f, Typeable g, Typeable k2, Typeable k1,
 Data (f (g x))) =>
Int -> (forall d. Data d => d -> u) -> (:.:) f g x -> u
forall k2 (f :: k2 -> *) k1 (g :: k1 -> k2) (x :: k1) u.
(Typeable x, Typeable f, Typeable g, Typeable k2, Typeable k1,
 Data (f (g x))) =>
(forall d. Data d => d -> u) -> (:.:) f g x -> [u]
forall k2 (f :: k2 -> *) k1 (g :: k1 -> k2) (x :: k1) r r'.
(Typeable x, Typeable f, Typeable g, Typeable k2, Typeable k1,
 Data (f (g x))) =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> (:.:) f g x -> r
forall k2 (f :: k2 -> *) k1 (g :: k1 -> k2) (x :: k1) r r'.
(Typeable x, Typeable f, Typeable g, Typeable k2, Typeable k1,
 Data (f (g x))) =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> (:.:) f g x -> r
forall k2 (f :: k2 -> *) k1 (g :: k1 -> k2) (x :: k1)
       (m :: * -> *).
(Typeable x, Typeable f, Typeable g, Typeable k2, Typeable k1,
 Data (f (g x)), Monad m) =>
(forall d. Data d => d -> m d) -> (:.:) f g x -> m ((:.:) f g x)
forall k2 (f :: k2 -> *) k1 (g :: k1 -> k2) (x :: k1)
       (m :: * -> *).
(Typeable x, Typeable f, Typeable g, Typeable k2, Typeable k1,
 Data (f (g x)), MonadPlus m) =>
(forall d. Data d => d -> m d) -> (:.:) f g x -> m ((:.:) f g x)
forall k2 (f :: k2 -> *) k1 (g :: k1 -> k2) (x :: k1)
       (c :: * -> *).
(Typeable x, Typeable f, Typeable g, Typeable k2, Typeable k1,
 Data (f (g x))) =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ((:.:) f g x)
forall k2 (f :: k2 -> *) k1 (g :: k1 -> k2) (x :: k1)
       (c :: * -> *).
(Typeable x, Typeable f, Typeable g, Typeable k2, Typeable k1,
 Data (f (g x))) =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> (:.:) f g x -> c ((:.:) f g x)
forall k2 (f :: k2 -> *) k1 (g :: k1 -> k2) (x :: k1) (t :: * -> *)
       (c :: * -> *).
(Typeable x, Typeable f, Typeable g, Typeable k2, Typeable k1,
 Data (f (g x)), Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c ((:.:) f g x))
forall k2 (f :: k2 -> *) k1 (g :: k1 -> k2) (x :: k1)
       (t :: * -> * -> *) (c :: * -> *).
(Typeable x, Typeable f, Typeable g, Typeable k2, Typeable k1,
 Data (f (g x)), Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ((:.:) f g x))
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> (:.:) f g x -> m ((:.:) f g x)
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> (:.:) f g x -> m ((:.:) f g x)
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ((:.:) f g x)
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> (:.:) f g x -> c ((:.:) f g x)
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ((:.:) f g x))
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ((:.:) f g x))
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> (:.:) f g x -> m ((:.:) f g x)
$cgmapMo :: forall k2 (f :: k2 -> *) k1 (g :: k1 -> k2) (x :: k1)
       (m :: * -> *).
(Typeable x, Typeable f, Typeable g, Typeable k2, Typeable k1,
 Data (f (g x)), MonadPlus m) =>
(forall d. Data d => d -> m d) -> (:.:) f g x -> m ((:.:) f g x)
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> (:.:) f g x -> m ((:.:) f g x)
$cgmapMp :: forall k2 (f :: k2 -> *) k1 (g :: k1 -> k2) (x :: k1)
       (m :: * -> *).
(Typeable x, Typeable f, Typeable g, Typeable k2, Typeable k1,
 Data (f (g x)), MonadPlus m) =>
(forall d. Data d => d -> m d) -> (:.:) f g x -> m ((:.:) f g x)
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> (:.:) f g x -> m ((:.:) f g x)
$cgmapM :: forall k2 (f :: k2 -> *) k1 (g :: k1 -> k2) (x :: k1)
       (m :: * -> *).
(Typeable x, Typeable f, Typeable g, Typeable k2, Typeable k1,
 Data (f (g x)), Monad m) =>
(forall d. Data d => d -> m d) -> (:.:) f g x -> m ((:.:) f g x)
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> (:.:) f g x -> u
$cgmapQi :: forall k2 (f :: k2 -> *) k1 (g :: k1 -> k2) (x :: k1) u.
(Typeable x, Typeable f, Typeable g, Typeable k2, Typeable k1,
 Data (f (g x))) =>
Int -> (forall d. Data d => d -> u) -> (:.:) f g x -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> (:.:) f g x -> [u]
$cgmapQ :: forall k2 (f :: k2 -> *) k1 (g :: k1 -> k2) (x :: k1) u.
(Typeable x, Typeable f, Typeable g, Typeable k2, Typeable k1,
 Data (f (g x))) =>
(forall d. Data d => d -> u) -> (:.:) f g x -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> (:.:) f g x -> r
$cgmapQr :: forall k2 (f :: k2 -> *) k1 (g :: k1 -> k2) (x :: k1) r r'.
(Typeable x, Typeable f, Typeable g, Typeable k2, Typeable k1,
 Data (f (g x))) =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> (:.:) f g x -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> (:.:) f g x -> r
$cgmapQl :: forall k2 (f :: k2 -> *) k1 (g :: k1 -> k2) (x :: k1) r r'.
(Typeable x, Typeable f, Typeable g, Typeable k2, Typeable k1,
 Data (f (g x))) =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> (:.:) f g x -> r
gmapT :: (forall b. Data b => b -> b) -> (:.:) f g x -> (:.:) f g x
$cgmapT :: forall k2 (f :: k2 -> *) k1 (g :: k1 -> k2) (x :: k1).
(Typeable x, Typeable f, Typeable g, Typeable k2, Typeable k1,
 Data (f (g x))) =>
(forall b. Data b => b -> b) -> (:.:) f g x -> (:.:) f g x
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ((:.:) f g x))
$cdataCast2 :: forall k2 (f :: k2 -> *) k1 (g :: k1 -> k2) (x :: k1)
       (t :: * -> * -> *) (c :: * -> *).
(Typeable x, Typeable f, Typeable g, Typeable k2, Typeable k1,
 Data (f (g x)), Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ((:.:) f g x))
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ((:.:) f g x))
$cdataCast1 :: forall k2 (f :: k2 -> *) k1 (g :: k1 -> k2) (x :: k1) (t :: * -> *)
       (c :: * -> *).
(Typeable x, Typeable f, Typeable g, Typeable k2, Typeable k1,
 Data (f (g x)), Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c ((:.:) f g x))
dataTypeOf :: (:.:) f g x -> DataType
$cdataTypeOf :: forall k2 (f :: k2 -> *) k1 (g :: k1 -> k2) (x :: k1).
(Typeable x, Typeable f, Typeable g, Typeable k2, Typeable k1,
 Data (f (g x))) =>
(:.:) f g x -> DataType
toConstr :: (:.:) f g x -> Constr
$ctoConstr :: forall k2 (f :: k2 -> *) k1 (g :: k1 -> k2) (x :: k1).
(Typeable x, Typeable f, Typeable g, Typeable k2, Typeable k1,
 Data (f (g x))) =>
(:.:) f g x -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ((:.:) f g x)
$cgunfold :: forall k2 (f :: k2 -> *) k1 (g :: k1 -> k2) (x :: k1)
       (c :: * -> *).
(Typeable x, Typeable f, Typeable g, Typeable k2, Typeable k1,
 Data (f (g x))) =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ((:.:) f g x)
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> (:.:) f g x -> c ((:.:) f g x)
$cgfoldl :: forall k2 (f :: k2 -> *) k1 (g :: k1 -> k2) (x :: k1)
       (c :: * -> *).
(Typeable x, Typeable f, Typeable g, Typeable k2, Typeable k1,
 Data (f (g x))) =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> (:.:) f g x -> c ((:.:) f g x)
Data
                 , (forall a b. (a -> b) -> (:.:) f g a -> (:.:) f g b)
-> (forall a b. a -> (:.:) f g b -> (:.:) f g a)
-> Functor (f :.: g)
forall a b. a -> (:.:) f g b -> (:.:) f g a
forall a b. (a -> b) -> (:.:) f g a -> (:.:) f g b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
forall (f :: * -> *) (g :: * -> *) a b.
(Functor f, Functor g) =>
a -> (:.:) f g b -> (:.:) f g a
forall (f :: * -> *) (g :: * -> *) a b.
(Functor f, Functor g) =>
(a -> b) -> (:.:) f g a -> (:.:) f g b
<$ :: forall a b. a -> (:.:) f g b -> (:.:) f g a
$c<$ :: forall (f :: * -> *) (g :: * -> *) a b.
(Functor f, Functor g) =>
a -> (:.:) f g b -> (:.:) f g a
fmap :: forall a b. (a -> b) -> (:.:) f g a -> (:.:) f g b
$cfmap :: forall (f :: * -> *) (g :: * -> *) a b.
(Functor f, Functor g) =>
(a -> b) -> (:.:) f g a -> (:.:) f g b
Functor, (forall m. Monoid m => (:.:) f g m -> m)
-> (forall m a. Monoid m => (a -> m) -> (:.:) f g a -> m)
-> (forall m a. Monoid m => (a -> m) -> (:.:) f g a -> m)
-> (forall a b. (a -> b -> b) -> b -> (:.:) f g a -> b)
-> (forall a b. (a -> b -> b) -> b -> (:.:) f g a -> b)
-> (forall b a. (b -> a -> b) -> b -> (:.:) f g a -> b)
-> (forall b a. (b -> a -> b) -> b -> (:.:) f g a -> b)
-> (forall a. (a -> a -> a) -> (:.:) f g a -> a)
-> (forall a. (a -> a -> a) -> (:.:) f g a -> a)
-> (forall a. (:.:) f g a -> [a])
-> (forall a. (:.:) f g a -> Bool)
-> (forall a. (:.:) f g a -> Int)
-> (forall a. Eq a => a -> (:.:) f g a -> Bool)
-> (forall a. Ord a => (:.:) f g a -> a)
-> (forall a. Ord a => (:.:) f g a -> a)
-> (forall a. Num a => (:.:) f g a -> a)
-> (forall a. Num a => (:.:) f g a -> a)
-> Foldable (f :.: g)
forall a. Eq a => a -> (:.:) f g a -> Bool
forall a. Num a => (:.:) f g a -> a
forall a. Ord a => (:.:) f g a -> a
forall m. Monoid m => (:.:) f g m -> m
forall a. (:.:) f g a -> Bool
forall a. (:.:) f g a -> Int
forall a. (:.:) f g a -> [a]
forall a. (a -> a -> a) -> (:.:) f g a -> a
forall m a. Monoid m => (a -> m) -> (:.:) f g a -> m
forall b a. (b -> a -> b) -> b -> (:.:) f g a -> b
forall a b. (a -> b -> b) -> b -> (:.:) f g a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> Int)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
forall (f :: * -> *) (g :: * -> *) a.
(Foldable f, Foldable g, Eq a) =>
a -> (:.:) f g a -> Bool
forall (f :: * -> *) (g :: * -> *) a.
(Foldable f, Foldable g, Num a) =>
(:.:) f g a -> a
forall (f :: * -> *) (g :: * -> *) a.
(Foldable f, Foldable g, Ord a) =>
(:.:) f g a -> a
forall (f :: * -> *) (g :: * -> *) m.
(Foldable f, Foldable g, Monoid m) =>
(:.:) f g m -> m
forall (f :: * -> *) (g :: * -> *) a.
(Foldable f, Foldable g) =>
(:.:) f g a -> Bool
forall (f :: * -> *) (g :: * -> *) a.
(Foldable f, Foldable g) =>
(:.:) f g a -> Int
forall (f :: * -> *) (g :: * -> *) a.
(Foldable f, Foldable g) =>
(:.:) f g a -> [a]
forall (f :: * -> *) (g :: * -> *) a.
(Foldable f, Foldable g) =>
(a -> a -> a) -> (:.:) f g a -> a
forall (f :: * -> *) (g :: * -> *) m a.
(Foldable f, Foldable g, Monoid m) =>
(a -> m) -> (:.:) f g a -> m
forall (f :: * -> *) (g :: * -> *) b a.
(Foldable f, Foldable g) =>
(b -> a -> b) -> b -> (:.:) f g a -> b
forall (f :: * -> *) (g :: * -> *) a b.
(Foldable f, Foldable g) =>
(a -> b -> b) -> b -> (:.:) f g a -> b
product :: forall a. Num a => (:.:) f g a -> a
$cproduct :: forall (f :: * -> *) (g :: * -> *) a.
(Foldable f, Foldable g, Num a) =>
(:.:) f g a -> a
sum :: forall a. Num a => (:.:) f g a -> a
$csum :: forall (f :: * -> *) (g :: * -> *) a.
(Foldable f, Foldable g, Num a) =>
(:.:) f g a -> a
minimum :: forall a. Ord a => (:.:) f g a -> a
$cminimum :: forall (f :: * -> *) (g :: * -> *) a.
(Foldable f, Foldable g, Ord a) =>
(:.:) f g a -> a
maximum :: forall a. Ord a => (:.:) f g a -> a
$cmaximum :: forall (f :: * -> *) (g :: * -> *) a.
(Foldable f, Foldable g, Ord a) =>
(:.:) f g a -> a
elem :: forall a. Eq a => a -> (:.:) f g a -> Bool
$celem :: forall (f :: * -> *) (g :: * -> *) a.
(Foldable f, Foldable g, Eq a) =>
a -> (:.:) f g a -> Bool
length :: forall a. (:.:) f g a -> Int
$clength :: forall (f :: * -> *) (g :: * -> *) a.
(Foldable f, Foldable g) =>
(:.:) f g a -> Int
null :: forall a. (:.:) f g a -> Bool
$cnull :: forall (f :: * -> *) (g :: * -> *) a.
(Foldable f, Foldable g) =>
(:.:) f g a -> Bool
toList :: forall a. (:.:) f g a -> [a]
$ctoList :: forall (f :: * -> *) (g :: * -> *) a.
(Foldable f, Foldable g) =>
(:.:) f g a -> [a]
foldl1 :: forall a. (a -> a -> a) -> (:.:) f g a -> a
$cfoldl1 :: forall (f :: * -> *) (g :: * -> *) a.
(Foldable f, Foldable g) =>
(a -> a -> a) -> (:.:) f g a -> a
foldr1 :: forall a. (a -> a -> a) -> (:.:) f g a -> a
$cfoldr1 :: forall (f :: * -> *) (g :: * -> *) a.
(Foldable f, Foldable g) =>
(a -> a -> a) -> (:.:) f g a -> a
foldl' :: forall b a. (b -> a -> b) -> b -> (:.:) f g a -> b
$cfoldl' :: forall (f :: * -> *) (g :: * -> *) b a.
(Foldable f, Foldable g) =>
(b -> a -> b) -> b -> (:.:) f g a -> b
foldl :: forall b a. (b -> a -> b) -> b -> (:.:) f g a -> b
$cfoldl :: forall (f :: * -> *) (g :: * -> *) b a.
(Foldable f, Foldable g) =>
(b -> a -> b) -> b -> (:.:) f g a -> b
foldr' :: forall a b. (a -> b -> b) -> b -> (:.:) f g a -> b
$cfoldr' :: forall (f :: * -> *) (g :: * -> *) a b.
(Foldable f, Foldable g) =>
(a -> b -> b) -> b -> (:.:) f g a -> b
foldr :: forall a b. (a -> b -> b) -> b -> (:.:) f g a -> b
$cfoldr :: forall (f :: * -> *) (g :: * -> *) a b.
(Foldable f, Foldable g) =>
(a -> b -> b) -> b -> (:.:) f g a -> b
foldMap' :: forall m a. Monoid m => (a -> m) -> (:.:) f g a -> m
$cfoldMap' :: forall (f :: * -> *) (g :: * -> *) m a.
(Foldable f, Foldable g, Monoid m) =>
(a -> m) -> (:.:) f g a -> m
foldMap :: forall m a. Monoid m => (a -> m) -> (:.:) f g a -> m
$cfoldMap :: forall (f :: * -> *) (g :: * -> *) m a.
(Foldable f, Foldable g, Monoid m) =>
(a -> m) -> (:.:) f g a -> m
fold :: forall m. Monoid m => (:.:) f g m -> m
$cfold :: forall (f :: * -> *) (g :: * -> *) m.
(Foldable f, Foldable g, Monoid m) =>
(:.:) f g m -> m
Foldable )
  deriving newtype (NonEmpty ((:.:) f g x) -> (:.:) f g x
(:.:) f g x -> (:.:) f g x -> (:.:) f g x
((:.:) f g x -> (:.:) f g x -> (:.:) f g x)
-> (NonEmpty ((:.:) f g x) -> (:.:) f g x)
-> (forall b. Integral b => b -> (:.:) f g x -> (:.:) f g x)
-> Semigroup ((:.:) f g x)
forall b. Integral b => b -> (:.:) f g x -> (:.:) f g x
forall a.
(a -> a -> a)
-> (NonEmpty a -> a)
-> (forall b. Integral b => b -> a -> a)
-> Semigroup a
forall k2 (f :: k2 -> *) k1 (g :: k1 -> k2) (x :: k1).
Semigroup (f (g x)) =>
NonEmpty ((:.:) f g x) -> (:.:) f g x
forall k2 (f :: k2 -> *) k1 (g :: k1 -> k2) (x :: k1).
Semigroup (f (g x)) =>
(:.:) f g x -> (:.:) f g x -> (:.:) f g x
forall k2 (f :: k2 -> *) k1 (g :: k1 -> k2) (x :: k1) b.
(Semigroup (f (g x)), Integral b) =>
b -> (:.:) f g x -> (:.:) f g x
stimes :: forall b. Integral b => b -> (:.:) f g x -> (:.:) f g x
$cstimes :: forall k2 (f :: k2 -> *) k1 (g :: k1 -> k2) (x :: k1) b.
(Semigroup (f (g x)), Integral b) =>
b -> (:.:) f g x -> (:.:) f g x
sconcat :: NonEmpty ((:.:) f g x) -> (:.:) f g x
$csconcat :: forall k2 (f :: k2 -> *) k1 (g :: k1 -> k2) (x :: k1).
Semigroup (f (g x)) =>
NonEmpty ((:.:) f g x) -> (:.:) f g x
<> :: (:.:) f g x -> (:.:) f g x -> (:.:) f g x
$c<> :: forall k2 (f :: k2 -> *) k1 (g :: k1 -> k2) (x :: k1).
Semigroup (f (g x)) =>
(:.:) f g x -> (:.:) f g x -> (:.:) f g x
Semigroup, Semigroup ((:.:) f g x)
(:.:) f g x
Semigroup ((:.:) f g x)
-> (:.:) f g x
-> ((:.:) f g x -> (:.:) f g x -> (:.:) f g x)
-> ([(:.:) f g x] -> (:.:) f g x)
-> Monoid ((:.:) f g x)
[(:.:) f g x] -> (:.:) f g x
(:.:) f g x -> (:.:) f g x -> (:.:) f g x
forall a.
Semigroup a -> a -> (a -> a -> a) -> ([a] -> a) -> Monoid a
forall {k2} {f :: k2 -> *} {k1} {g :: k1 -> k2} {x :: k1}.
Monoid (f (g x)) =>
Semigroup ((:.:) f g x)
forall k2 (f :: k2 -> *) k1 (g :: k1 -> k2) (x :: k1).
Monoid (f (g x)) =>
(:.:) f g x
forall k2 (f :: k2 -> *) k1 (g :: k1 -> k2) (x :: k1).
Monoid (f (g x)) =>
[(:.:) f g x] -> (:.:) f g x
forall k2 (f :: k2 -> *) k1 (g :: k1 -> k2) (x :: k1).
Monoid (f (g x)) =>
(:.:) f g x -> (:.:) f g x -> (:.:) f g x
mconcat :: [(:.:) f g x] -> (:.:) f g x
$cmconcat :: forall k2 (f :: k2 -> *) k1 (g :: k1 -> k2) (x :: k1).
Monoid (f (g x)) =>
[(:.:) f g x] -> (:.:) f g x
mappend :: (:.:) f g x -> (:.:) f g x -> (:.:) f g x
$cmappend :: forall k2 (f :: k2 -> *) k1 (g :: k1 -> k2) (x :: k1).
Monoid (f (g x)) =>
(:.:) f g x -> (:.:) f g x -> (:.:) f g x
mempty :: (:.:) f g x
$cmempty :: forall k2 (f :: k2 -> *) k1 (g :: k1 -> k2) (x :: k1).
Monoid (f (g x)) =>
(:.:) f g x
Monoid)

-- Note: kind specificity
--
-- I'd prefer to have the kinds inferred for @(:.:)@ and @MP@ rather than
-- specified. Unfortunately, I think it would be too confusing not to match the
-- types imported from GHC.Generics. See
-- https://gitlab.haskell.org/ghc/ghc/-/issues/20497

deriving stock instance (Traversable f, Traversable g) => Traversable (f :.: g)

deriving via forall (f :: Type -> Type) (g :: Type -> Type). f G.:.: g
  instance (Applicative f, Applicative g) => Applicative (f :.: g)

deriving via forall (f :: Type -> Type) (g :: Type -> Type). f G.:.: g
  instance (Alternative f, Applicative g) => Alternative (f :.: g)

deriving via forall (f :: Type -> Type) (g :: Type -> Type). f G.:.: g
  instance (Functor f, Contravariant g) => Contravariant (f :.: g)

instance (Eq1 f, Eq1 g) => Eq1 (f :.: g) where
  liftEq :: forall a b. (a -> b -> Bool) -> (:.:) f g a -> (:.:) f g b -> Bool
liftEq a -> b -> Bool
eq (Comp1 f (g a)
x) (Comp1 f (g b)
y) = (g a -> g b -> Bool) -> f (g a) -> f (g b) -> Bool
forall (f :: * -> *) a b.
Eq1 f =>
(a -> b -> Bool) -> f a -> f b -> Bool
liftEq ((a -> b -> Bool) -> g a -> g b -> Bool
forall (f :: * -> *) a b.
Eq1 f =>
(a -> b -> Bool) -> f a -> f b -> Bool
liftEq a -> b -> Bool
eq) f (g a)
x f (g b)
y

instance (Ord1 f, Ord1 g) => Ord1 (f :.: g) where
  liftCompare :: forall a b.
(a -> b -> Ordering) -> (:.:) f g a -> (:.:) f g b -> Ordering
liftCompare a -> b -> Ordering
cmp (Comp1 f (g a)
x) (Comp1 f (g b)
y) = (g a -> g b -> Ordering) -> f (g a) -> f (g b) -> Ordering
forall (f :: * -> *) a b.
Ord1 f =>
(a -> b -> Ordering) -> f a -> f b -> Ordering
liftCompare ((a -> b -> Ordering) -> g a -> g b -> Ordering
forall (f :: * -> *) a b.
Ord1 f =>
(a -> b -> Ordering) -> f a -> f b -> Ordering
liftCompare a -> b -> Ordering
cmp) f (g a)
x f (g b)
y

instance (Show1 f, Show1 g) => Show1 (f :.: g) where
  liftShowsPrec :: forall a.
(Int -> a -> ShowS)
-> ([a] -> ShowS) -> Int -> (:.:) f g a -> ShowS
liftShowsPrec Int -> a -> ShowS
sp [a] -> ShowS
sl Int
d (Comp1 f (g a)
x) =
      (Int -> f (g a) -> ShowS) -> String -> Int -> f (g a) -> ShowS
forall a. (Int -> a -> ShowS) -> String -> Int -> a -> ShowS
showsUnaryWith ((Int -> g a -> ShowS)
-> ([g a] -> ShowS) -> Int -> f (g a) -> ShowS
forall (f :: * -> *) a.
Show1 f =>
(Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> f a -> ShowS
liftShowsPrec Int -> g a -> ShowS
sp' [g a] -> ShowS
sl') String
"Comp1" Int
d f (g a)
x
    where
      sp' :: Int -> g a -> ShowS
sp' = (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> g a -> ShowS
forall (f :: * -> *) a.
Show1 f =>
(Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> f a -> ShowS
liftShowsPrec Int -> a -> ShowS
sp [a] -> ShowS
sl
      sl' :: [g a] -> ShowS
sl' = (Int -> a -> ShowS) -> ([a] -> ShowS) -> [g a] -> ShowS
forall (f :: * -> *) a.
Show1 f =>
(Int -> a -> ShowS) -> ([a] -> ShowS) -> [f a] -> ShowS
liftShowList Int -> a -> ShowS
sp [a] -> ShowS
sl

instance (Read1 f, Read1 g) => Read1 (f :.: g) where
  liftReadPrec :: forall a. ReadPrec a -> ReadPrec [a] -> ReadPrec ((:.:) f g a)
liftReadPrec ReadPrec a
rp ReadPrec [a]
rl = ReadPrec ((:.:) f g a) -> ReadPrec ((:.:) f g a)
forall a. ReadPrec a -> ReadPrec a
readData (ReadPrec ((:.:) f g a) -> ReadPrec ((:.:) f g a))
-> ReadPrec ((:.:) f g a) -> ReadPrec ((:.:) f g a)
forall a b. (a -> b) -> a -> b
$
      ReadPrec (f (g a))
-> String -> (f (g a) -> (:.:) f g a) -> ReadPrec ((:.:) f g a)
forall a t. ReadPrec a -> String -> (a -> t) -> ReadPrec t
readUnaryWith (ReadPrec (g a) -> ReadPrec [g a] -> ReadPrec (f (g a))
forall (f :: * -> *) a.
Read1 f =>
ReadPrec a -> ReadPrec [a] -> ReadPrec (f a)
liftReadPrec ReadPrec (g a)
rp' ReadPrec [g a]
rl') String
"Comp1" f (g a) -> (:.:) f g a
forall k2 k1 (f :: k2 -> *) (g :: k1 -> k2) (x :: k1).
f (g x) -> (:.:) f g x
Comp1
    where
      rp' :: ReadPrec (g a)
rp' = ReadPrec a -> ReadPrec [a] -> ReadPrec (g a)
forall (f :: * -> *) a.
Read1 f =>
ReadPrec a -> ReadPrec [a] -> ReadPrec (f a)
liftReadPrec     ReadPrec a
rp ReadPrec [a]
rl
      rl' :: ReadPrec [g a]
rl' = ReadPrec a -> ReadPrec [a] -> ReadPrec [g a]
forall (f :: * -> *) a.
Read1 f =>
ReadPrec a -> ReadPrec [a] -> ReadPrec [f a]
liftReadListPrec ReadPrec a
rp ReadPrec [a]
rl

  liftReadListPrec :: forall a. ReadPrec a -> ReadPrec [a] -> ReadPrec [(:.:) f g a]
liftReadListPrec = ReadPrec a -> ReadPrec [a] -> ReadPrec [(:.:) f g a]
forall (f :: * -> *) a.
Read1 f =>
ReadPrec a -> ReadPrec [a] -> ReadPrec [f a]
liftReadListPrecDefault
  liftReadList :: forall a. (Int -> ReadS a) -> ReadS [a] -> ReadS [(:.:) f g a]
liftReadList     = (Int -> ReadS a) -> ReadS [a] -> ReadS [(:.:) f g a]
forall (f :: * -> *) a.
Read1 f =>
(Int -> ReadS a) -> ReadS [a] -> ReadS [f a]
liftReadListDefault

-- | Types with nonlinear or multiplicity-polymorphic fields should use @MP1@
-- under @S1@. Unfortunately, Template Haskell (and GHC Generics) currently
-- lack any support for such types, so their instances must currently be
-- written entirely manually. We may add some functions to ease the pain at
-- some point.
--
-- Generic-deriving classes that do not involve linear types should treat
-- @MP1 m@ much as they treat @M1@: dig through it to get to the meat.
-- Unfortunately, some futzing about may be necessary to convince the
-- type checker that multiplicities work out.
--
-- Generic-deriving classes that use linear types may have to treat @MP1 m@
-- specially. In particular, they may need to constrain @m@ to be
-- ''GHC.Types.One' or ''GHC.Types.Many', or to match some other type
-- variable.
data MP1 :: forall k. Multiplicity -> (k -> Type) -> k -> Type where
-- See Note: kind specificity

-- If anything changes here (e.g., we add a field selector), then
-- the generic instances below will have to change.
  MP1 :: f a %m-> MP1 m f a

unMP1 :: MP1 m f a %n-> f a
-- Making this a field selector seems to break the type of the @MP1@
-- constructor. Whoops!
unMP1 :: forall {k} (m :: Multiplicity) (f :: k -> *) (a :: k)
       (n :: Multiplicity).
MP1 m f a %n -> f a
unMP1 (MP1 f a
fa) = f a
fa

deriving instance G.Generic (MP1 m f a)
deriving instance G.Generic1 (MP1 m f)
-- TODO: Give MP1 Generic and Generic1 instances!

instance Functor f => Functor (MP1 m f) where
  fmap :: forall a b. (a -> b) -> MP1 m f a -> MP1 m f b
fmap a -> b
f (MP1 f a
fa) = f b %m -> MP1 m f b
forall {k} (f :: k -> *) (a :: k) (m :: Multiplicity).
f a %m -> MP1 m f a
MP1 ((a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
f f a
fa)
  a
x <$ :: forall a b. a -> MP1 m f b -> MP1 m f a
<$ MP1 f b
fa = f a %m -> MP1 m f a
forall {k} (f :: k -> *) (a :: k) (m :: Multiplicity).
f a %m -> MP1 m f a
MP1 (a
x a -> f b -> f a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ f b
fa)

instance Applicative f => Applicative (MP1 m f) where
  -- Why can't we use pure = MP1 Prelude.. pure ?
  pure :: forall a. a -> MP1 m f a
pure a
a = f a %m -> MP1 m f a
forall {k} (f :: k -> *) (a :: k) (m :: Multiplicity).
f a %m -> MP1 m f a
MP1 (a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure a
a)
  liftA2 :: forall a b c. (a -> b -> c) -> MP1 m f a -> MP1 m f b -> MP1 m f c
liftA2 a -> b -> c
f (MP1 f a
x) (MP1 f b
y) = f c %m -> MP1 m f c
forall {k} (f :: k -> *) (a :: k) (m :: Multiplicity).
f a %m -> MP1 m f a
MP1 ((a -> b -> c) -> f a -> f b -> f c
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 a -> b -> c
f f a
x f b
y)

instance Monad f => Monad (MP1 m f) where
  MP1 f a
fa >>= :: forall a b. MP1 m f a -> (a -> MP1 m f b) -> MP1 m f b
>>= a -> MP1 m f b
f = f b %m -> MP1 m f b
forall {k} (f :: k -> *) (a :: k) (m :: Multiplicity).
f a %m -> MP1 m f a
MP1 (f a
fa f a -> (a -> f b) -> f b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= MP1 m f b -> f b
forall {k} (m :: Multiplicity) (f :: k -> *) (a :: k)
       (n :: Multiplicity).
MP1 m f a %n -> f a
unMP1 (MP1 m f b -> f b) -> (a -> MP1 m f b) -> a -> f b
forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. a -> MP1 m f b
f)

instance Foldable f => Foldable (MP1 m f) where
  foldMap :: forall m a. Monoid m => (a -> m) -> MP1 m f a -> m
foldMap a -> m
f (MP1 f a
x) = (a -> m) -> f a -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap a -> m
f f a
x
  foldMap' :: forall m a. Monoid m => (a -> m) -> MP1 m f a -> m
foldMap' a -> m
f (MP1 f a
x) = (a -> m) -> f a -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap' a -> m
f f a
x
  fold :: forall m. Monoid m => MP1 m f m -> m
fold (MP1 f m
x) = f m -> m
forall (t :: * -> *) m. (Foldable t, Monoid m) => t m -> m
fold f m
x
  foldr :: forall a b. (a -> b -> b) -> b -> MP1 m f a -> b
foldr a -> b -> b
c b
n (MP1 f a
x) = (a -> b -> b) -> b -> f a -> b
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr a -> b -> b
c b
n f a
x
  foldr' :: forall a b. (a -> b -> b) -> b -> MP1 m f a -> b
foldr' a -> b -> b
c b
n (MP1 f a
x) = (a -> b -> b) -> b -> f a -> b
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr' a -> b -> b
c b
n f a
x
  foldl :: forall b a. (b -> a -> b) -> b -> MP1 m f a -> b
foldl b -> a -> b
c b
n (MP1 f a
x) = (b -> a -> b) -> b -> f a -> b
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl b -> a -> b
c b
n f a
x
  foldl' :: forall b a. (b -> a -> b) -> b -> MP1 m f a -> b
foldl' b -> a -> b
c b
n (MP1 f a
x) = (b -> a -> b) -> b -> f a -> b
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' b -> a -> b
c b
n f a
x
  length :: forall a. MP1 m f a -> Int
length (MP1 f a
x) = f a -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length f a
x
  null :: forall a. MP1 m f a -> Bool
null (MP1 f a
x) = f a -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null f a
x
  elem :: forall a. Eq a => a -> MP1 m f a -> Bool
elem a
e (MP1 f a
x) = a -> f a -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
elem a
e f a
x
  maximum :: forall a. Ord a => MP1 m f a -> a
maximum (MP1 f a
x) = f a -> a
forall (t :: * -> *) a. (Foldable t, Ord a) => t a -> a
maximum f a
x
  minimum :: forall a. Ord a => MP1 m f a -> a
minimum (MP1 f a
x) = f a -> a
forall (t :: * -> *) a. (Foldable t, Ord a) => t a -> a
minimum f a
x
  sum :: forall a. Num a => MP1 m f a -> a
sum (MP1 f a
x) = f a -> a
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum f a
x
  product :: forall a. Num a => MP1 m f a -> a
product (MP1 f a
x) = f a -> a
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
product f a
x

instance Traversable f => Traversable (MP1 m f) where
  traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> MP1 m f a -> f (MP1 m f b)
traverse a -> f b
f (MP1 f a
x) = f b -> MP1 m f b
forall {k} (f :: k -> *) (a :: k) (m :: Multiplicity).
f a -> MP1 m f a
wrapMP1 (f b -> MP1 m f b) -> f (f b) -> f (MP1 m f b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (a -> f b) -> f a -> f (f b)
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse a -> f b
f f a
x
  sequenceA :: forall (f :: * -> *) a.
Applicative f =>
MP1 m f (f a) -> f (MP1 m f a)
sequenceA (MP1 f (f a)
x) = f a -> MP1 m f a
forall {k} (f :: k -> *) (a :: k) (m :: Multiplicity).
f a -> MP1 m f a
wrapMP1 (f a -> MP1 m f a) -> f (f a) -> f (MP1 m f a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> f (f a) -> f (f a)
forall (t :: * -> *) (f :: * -> *) a.
(Traversable t, Applicative f) =>
t (f a) -> f (t a)
sequenceA f (f a)
x
  mapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> MP1 m f a -> m (MP1 m f b)
mapM a -> m b
f (MP1 f a
x) = f b -> MP1 m f b
forall {k} (f :: k -> *) (a :: k) (m :: Multiplicity).
f a -> MP1 m f a
wrapMP1 (f b -> MP1 m f b) -> m (f b) -> m (MP1 m f b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (a -> m b) -> f a -> m (f b)
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM a -> m b
f f a
x
  sequence :: forall (m :: * -> *) a. Monad m => MP1 m f (m a) -> m (MP1 m f a)
sequence (MP1 f (m a)
x) = f a -> MP1 m f a
forall {k} (f :: k -> *) (a :: k) (m :: Multiplicity).
f a -> MP1 m f a
wrapMP1 (f a -> MP1 m f a) -> m (f a) -> m (MP1 m f a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> f (m a) -> m (f a)
forall (t :: * -> *) (m :: * -> *) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
sequence f (m a)
x

instance Contravariant f => Contravariant (MP1 m f) where
  contramap :: forall a' a. (a' -> a) -> MP1 m f a -> MP1 m f a'
contramap a' -> a
f (MP1 f a
x) = f a' %m -> MP1 m f a'
forall {k} (f :: k -> *) (a :: k) (m :: Multiplicity).
f a %m -> MP1 m f a
MP1 ((a' -> a) -> f a -> f a'
forall (f :: * -> *) a' a.
Contravariant f =>
(a' -> a) -> f a -> f a'
contramap a' -> a
f f a
x)
  b
a >$ :: forall b a. b -> MP1 m f b -> MP1 m f a
>$ MP1 f b
x = f a %m -> MP1 m f a
forall {k} (f :: k -> *) (a :: k) (m :: Multiplicity).
f a %m -> MP1 m f a
MP1 (b
a b -> f b -> f a
forall (f :: * -> *) b a. Contravariant f => b -> f b -> f a
>$ f b
x)

instance Alternative f => Alternative (MP1 m f) where
  empty :: forall a. MP1 m f a
empty = f a %m -> MP1 m f a
forall {k} (f :: k -> *) (a :: k) (m :: Multiplicity).
f a %m -> MP1 m f a
MP1 f a
forall (f :: * -> *) a. Alternative f => f a
empty
  MP1 f a
x <|> :: forall a. MP1 m f a -> MP1 m f a -> MP1 m f a
<|> MP1 f a
y = f a %m -> MP1 m f a
forall {k} (f :: k -> *) (a :: k) (m :: Multiplicity).
f a %m -> MP1 m f a
MP1 (f a
x f a -> f a -> f a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> f a
y)
  many :: forall a. MP1 m f a -> MP1 m f [a]
many (MP1 f a
x) = f [a] %m -> MP1 m f [a]
forall {k} (f :: k -> *) (a :: k) (m :: Multiplicity).
f a %m -> MP1 m f a
MP1 (f a -> f [a]
forall (f :: * -> *) a. Alternative f => f a -> f [a]
many f a
x)
  some :: forall a. MP1 m f a -> MP1 m f [a]
some (MP1 f a
x) = f [a] %m -> MP1 m f [a]
forall {k} (f :: k -> *) (a :: k) (m :: Multiplicity).
f a %m -> MP1 m f a
MP1 (f a -> f [a]
forall (f :: * -> *) a. Alternative f => f a -> f [a]
some f a
x)

instance MonadPlus f => MonadPlus (MP1 m f) where
  mzero :: forall a. MP1 m f a
mzero = f a %m -> MP1 m f a
forall {k} (f :: k -> *) (a :: k) (m :: Multiplicity).
f a %m -> MP1 m f a
MP1 f a
forall (m :: * -> *) a. MonadPlus m => m a
mzero
  mplus :: forall a. MP1 m f a -> MP1 m f a -> MP1 m f a
mplus (MP1 f a
x) (MP1 f a
y) = f a %m -> MP1 m f a
forall {k} (f :: k -> *) (a :: k) (m :: Multiplicity).
f a %m -> MP1 m f a
MP1 (f a -> f a -> f a
forall (m :: * -> *) a. MonadPlus m => m a -> m a -> m a
mplus f a
x f a
y)

deriving instance Eq (f a) => Eq (MP1 m f a)
instance Ord (f a) => Ord (MP1 m f a) where
  compare :: MP1 m f a -> MP1 m f a -> Ordering
compare (MP1 f a
a) (MP1 f a
b) = f a -> f a -> Ordering
forall a. Ord a => a -> a -> Ordering
compare f a
a f a
b
  MP1 f a
a < :: MP1 m f a -> MP1 m f a -> Bool
< MP1 f a
b = f a
a f a -> f a -> Bool
forall a. Ord a => a -> a -> Bool
< f a
b
  MP1 f a
a <= :: MP1 m f a -> MP1 m f a -> Bool
<= MP1 f a
b = f a
a f a -> f a -> Bool
forall a. Ord a => a -> a -> Bool
<= f a
b
  MP1 f a
a > :: MP1 m f a -> MP1 m f a -> Bool
> MP1 f a
b = f a
a f a -> f a -> Bool
forall a. Ord a => a -> a -> Bool
> f a
b
  MP1 f a
a >= :: MP1 m f a -> MP1 m f a -> Bool
>= MP1 f a
b = f a
a f a -> f a -> Bool
forall a. Ord a => a -> a -> Bool
>= f a
b
  min :: MP1 m f a -> MP1 m f a -> MP1 m f a
min (MP1 f a
a) (MP1 f a
b) = f a %m -> MP1 m f a
forall {k} (f :: k -> *) (a :: k) (m :: Multiplicity).
f a %m -> MP1 m f a
MP1 (f a -> f a -> f a
forall a. Ord a => a -> a -> a
min f a
a f a
b)
  max :: MP1 m f a -> MP1 m f a -> MP1 m f a
max (MP1 f a
a) (MP1 f a
b) = f a %m -> MP1 m f a
forall {k} (f :: k -> *) (a :: k) (m :: Multiplicity).
f a %m -> MP1 m f a
MP1 (f a -> f a -> f a
forall a. Ord a => a -> a -> a
max f a
a f a
b)

deriving instance Read (f a) => Read (MP1 m f a)
deriving instance Show (f a) => Show (MP1 m f a)

instance Semigroup (f a) => Semigroup (MP1 m f a) where
  MP1 f a
x <> :: MP1 m f a -> MP1 m f a -> MP1 m f a
<> MP1 f a
y = f a %m -> MP1 m f a
forall {k} (f :: k -> *) (a :: k) (m :: Multiplicity).
f a %m -> MP1 m f a
MP1 (f a
x f a -> f a -> f a
forall a. Semigroup a => a -> a -> a
<> f a
y)
  stimes :: forall b. Integral b => b -> MP1 m f a -> MP1 m f a
stimes b
n (MP1 f a
x) = f a %m -> MP1 m f a
forall {k} (f :: k -> *) (a :: k) (m :: Multiplicity).
f a %m -> MP1 m f a
MP1 (b -> f a -> f a
forall a b. (Semigroup a, Integral b) => b -> a -> a
stimes b
n f a
x)
  sconcat :: NonEmpty (MP1 m f a) -> MP1 m f a
sconcat NonEmpty (MP1 m f a)
x = f a %m -> MP1 m f a
forall {k} (f :: k -> *) (a :: k) (m :: Multiplicity).
f a %m -> MP1 m f a
MP1 (NonEmpty (f a) -> f a
forall a. Semigroup a => NonEmpty a -> a
sconcat ((MP1 m f a -> f a) -> NonEmpty (MP1 m f a) -> NonEmpty (f a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap MP1 m f a -> f a
forall {k} (m :: Multiplicity) (f :: k -> *) (a :: k)
       (n :: Multiplicity).
MP1 m f a %n -> f a
unMP1 NonEmpty (MP1 m f a)
x))

instance Monoid (f a) => Monoid (MP1 m f a) where
  mempty :: MP1 m f a
mempty = f a %m -> MP1 m f a
forall {k} (f :: k -> *) (a :: k) (m :: Multiplicity).
f a %m -> MP1 m f a
MP1 f a
forall a. Monoid a => a
mempty

-- -------------------
-- Lifted instances

instance Eq1 f => Eq1 (MP1 m f) where
  liftEq :: forall a b. (a -> b -> Bool) -> MP1 m f a -> MP1 m f b -> Bool
liftEq a -> b -> Bool
eq (MP1 f a
x) (MP1 f b
y) = (a -> b -> Bool) -> f a -> f b -> Bool
forall (f :: * -> *) a b.
Eq1 f =>
(a -> b -> Bool) -> f a -> f b -> Bool
liftEq a -> b -> Bool
eq f a
x f b
y

instance Ord1 f => Ord1 (MP1 m f) where
  liftCompare :: forall a b.
(a -> b -> Ordering) -> MP1 m f a -> MP1 m f b -> Ordering
liftCompare a -> b -> Ordering
cmp (MP1 f a
x) (MP1 f b
y) = (a -> b -> Ordering) -> f a -> f b -> Ordering
forall (f :: * -> *) a b.
Ord1 f =>
(a -> b -> Ordering) -> f a -> f b -> Ordering
liftCompare a -> b -> Ordering
cmp f a
x f b
y

instance Show1 f => Show1 (MP1 m f) where
  liftShowsPrec :: forall a.
(Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> MP1 m f a -> ShowS
liftShowsPrec Int -> a -> ShowS
sp [a] -> ShowS
sl Int
d (MP1 f a
a) = (Int -> f a -> ShowS) -> String -> Int -> f a -> ShowS
forall a. (Int -> a -> ShowS) -> String -> Int -> a -> ShowS
showsUnaryWith ((Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> f a -> ShowS
forall (f :: * -> *) a.
Show1 f =>
(Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> f a -> ShowS
liftShowsPrec Int -> a -> ShowS
sp [a] -> ShowS
sl) String
"MP1" Int
d f a
a

instance Read1 f => Read1 (MP1 m f) where
  liftReadPrec :: forall a. ReadPrec a -> ReadPrec [a] -> ReadPrec (MP1 m f a)
liftReadPrec ReadPrec a
rp ReadPrec [a]
rl = ReadPrec (MP1 m f a) -> ReadPrec (MP1 m f a)
forall a. ReadPrec a -> ReadPrec a
readData (ReadPrec (MP1 m f a) -> ReadPrec (MP1 m f a))
-> ReadPrec (MP1 m f a) -> ReadPrec (MP1 m f a)
forall a b. (a -> b) -> a -> b
$
    ReadPrec (f a)
-> String -> (f a -> MP1 m f a) -> ReadPrec (MP1 m f a)
forall a t. ReadPrec a -> String -> (a -> t) -> ReadPrec t
readUnaryWith (ReadPrec a -> ReadPrec [a] -> ReadPrec (f a)
forall (f :: * -> *) a.
Read1 f =>
ReadPrec a -> ReadPrec [a] -> ReadPrec (f a)
liftReadPrec ReadPrec a
rp ReadPrec [a]
rl) String
"MP1" (\f a
x -> f a %m -> MP1 m f a
forall {k} (f :: k -> *) (a :: k) (m :: Multiplicity).
f a %m -> MP1 m f a
MP1 f a
x)
  liftReadListPrec :: forall a. ReadPrec a -> ReadPrec [a] -> ReadPrec [MP1 m f a]
liftReadListPrec = ReadPrec a -> ReadPrec [a] -> ReadPrec [MP1 m f a]
forall (f :: * -> *) a.
Read1 f =>
ReadPrec a -> ReadPrec [a] -> ReadPrec [f a]
liftReadListPrecDefault
  liftReadList :: forall a. (Int -> ReadS a) -> ReadS [a] -> ReadS [MP1 m f a]
liftReadList     = (Int -> ReadS a) -> ReadS [a] -> ReadS [MP1 m f a]
forall (f :: * -> *) a.
Read1 f =>
(Int -> ReadS a) -> ReadS [a] -> ReadS [f a]
liftReadListDefault

-- -------------------
-- Data instance

-- For some reason, the derived Data instance produces a multiplicity mismatch.
-- *sigh*.
instance (Typeable m, Typeable f, Data a, Data (f a)) => Data (MP1 m f a) where
  gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> MP1 m f a -> c (MP1 m f a)
gfoldl forall d b. Data d => c (d -> b) -> d -> c b
f forall g. g -> c g
g (MP1 f a
fa) = ((f a -> MP1 m f a) -> c (f a -> MP1 m f a)
forall g. g -> c g
g f a -> MP1 m f a
forall {k} (f :: k -> *) (a :: k) (m :: Multiplicity).
f a -> MP1 m f a
wrapMP1 c (f a -> MP1 m f a) -> f a -> c (MP1 m f a)
forall d b. Data d => c (d -> b) -> d -> c b
`f` f a
fa)
  gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (MP1 m f a)
gunfold forall b r. Data b => c (b -> r) -> c r
f forall r. r -> c r
g Constr
_constr = c (f a -> MP1 m f a) -> c (MP1 m f a)
forall b r. Data b => c (b -> r) -> c r
f ((f a -> MP1 m f a) -> c (f a -> MP1 m f a)
forall r. r -> c r
g f a -> MP1 m f a
forall {k} (f :: k -> *) (a :: k) (m :: Multiplicity).
f a -> MP1 m f a
wrapMP1)
  toConstr :: MP1 m f a -> Constr
toConstr (MP1 f a
_) = Constr
mpConstr
  dataTypeOf :: MP1 m f a -> DataType
dataTypeOf MP1 m f a
_ = DataType
mpDataType
  dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (MP1 m f a))
dataCast1 forall d. Data d => c (t d)
mp = c (t a) -> Maybe (c (MP1 m f a))
forall {k1} {k2} (c :: k1 -> *) (t :: k2 -> k1) (t' :: k2 -> k1)
       (a :: k2).
(Typeable t, Typeable t') =>
c (t a) -> Maybe (c (t' a))
gcast1 c (t a)
forall d. Data d => c (t d)
mp

mpDataType :: D.DataType
mpDataType :: DataType
mpDataType = String -> [Constr] -> DataType
D.mkDataType String
"MP1" [Constr
mpConstr]

mpConstr :: D.Constr
mpConstr :: Constr
mpConstr = DataType -> String -> [String] -> Fixity -> Constr
D.mkConstr DataType
mpDataType String
"MP1" [] Fixity
D.Prefix

-- Why do we need this?
wrapMP1 :: f a -> MP1 m f a
wrapMP1 :: forall {k} (f :: k -> *) (a :: k) (m :: Multiplicity).
f a -> MP1 m f a
wrapMP1 f a
fa = f a %m -> MP1 m f a
forall {k} (f :: k -> *) (a :: k) (m :: Multiplicity).
f a %m -> MP1 m f a
MP1 f a
fa

-- -----------------
-- Generic instances for MP1 (ugh)

-- | This type is used solely to get the name of this very module and the
-- package it's in, reliably. It must be in the same module as 'MP1'!

data ForInfo deriving (forall x. ForInfo -> Rep ForInfo x)
-> (forall x. Rep ForInfo x -> ForInfo) -> Generic ForInfo
forall x. Rep ForInfo x -> ForInfo
forall x. ForInfo -> Rep ForInfo x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ForInfo x -> ForInfo
$cfrom :: forall x. ForInfo -> Rep ForInfo x
G.Generic

-- | @CopyPkgModule f g@ copies the module and package name from
-- representation @f@ to representation @g@. Everything else is left
-- alone.
type family CopyPkgModule (f :: j -> Type) (g :: k -> Type) :: k -> Type where
  CopyPkgModule (D1 ('MetaData _ mod_name pkg_name _) _)
                  (D1 ('MetaData type_name _ _ is_newtype) r)
    = D1 ('MetaData type_name mod_name pkg_name is_newtype) r

instance Generic (MP1 m f a) where
  type Rep (MP1 m f a) = CopyPkgModule (G.Rep ForInfo)
    (D1
       ('MetaData "MP1" "" "" 'False)
       (C1
          ('MetaCons "MP1" 'PrefixI 'False)
          (S1
             ('MetaSel
                'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy)
             (MP1 m (Rec0 (f a))))))
  from :: forall p (m :: Multiplicity). MP1 m f a %m -> Rep (MP1 m f a) p
from MP1 m f a
y = MP1 m f a %1 -> Rep (MP1 m f a) p
forall x. MP1 m f a %1 -> Rep (MP1 m f a) x
from' MP1 m f a
y
    where
      from' :: MP1 m f a %1 -> Rep (MP1 m f a) x
      from' :: forall x. MP1 m f a %1 -> Rep (MP1 m f a) x
from' (MP1 f a
x) = M1
  C
  ('MetaCons "MP1" 'PrefixI 'False)
  (M1
     S
     ('MetaSel
        'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy)
     (MP1 m (K1 R (f a))))
  x
%m -> M1
        D
        ('MetaData
           "MP1"
           "Generics.Linear.Class"
           "linear-generics-0.1.0.1-inplace"
           'False)
        (M1
           C
           ('MetaCons "MP1" 'PrefixI 'False)
           (M1
              S
              ('MetaSel
                 'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy)
              (MP1 m (K1 R (f a)))))
        x
forall k i (c :: Meta) (f :: k -> *) (p :: k). f p -> M1 i c f p
M1 (M1
  S
  ('MetaSel
     'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy)
  (MP1 m (K1 R (f a)))
  x
%m -> M1
        C
        ('MetaCons "MP1" 'PrefixI 'False)
        (M1
           S
           ('MetaSel
              'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy)
           (MP1 m (K1 R (f a))))
        x
forall k i (c :: Meta) (f :: k -> *) (p :: k). f p -> M1 i c f p
M1 (MP1 m (K1 R (f a)) x
%m -> M1
        S
        ('MetaSel
           'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy)
        (MP1 m (K1 R (f a)))
        x
forall k i (c :: Meta) (f :: k -> *) (p :: k). f p -> M1 i c f p
M1 (K1 R (f a) x %m -> MP1 m (K1 R (f a)) x
forall {k} (f :: k -> *) (a :: k) (m :: Multiplicity).
f a %m -> MP1 m f a
MP1 (f a %m -> K1 R (f a) x
forall k i c (p :: k). c -> K1 i c p
K1 f a
x))))
  to :: forall p (m :: Multiplicity). Rep (MP1 m f a) p %m -> MP1 m f a
to Rep (MP1 m f a) p
y = Rep (MP1 m f a) p %1 -> MP1 m f a
forall x. Rep (MP1 m f a) x %1 -> MP1 m f a
to' Rep (MP1 m f a) p
y
    where
      to' :: Rep (MP1 m f a) x %1 -> MP1 m f a
      to' :: forall x. Rep (MP1 m f a) x %1 -> MP1 m f a
to' (M1 (M1 (M1 (MP1 (K1 f a
x))))) = f a %m -> MP1 m f a
forall {k} (f :: k -> *) (a :: k) (m :: Multiplicity).
f a %m -> MP1 m f a
MP1 f a
x

instance Generic1 (MP1 m f) where
  type Rep1 (MP1 m f) = CopyPkgModule (G.Rep ForInfo)
    (D1
       ('MetaData "MP1" "" "" 'False)
       (C1
          ('MetaCons "MP1" 'PrefixI 'False)
          (S1
             ('MetaSel
                'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy)
             (MP1 m (Par1 :.: f)))))
  from1 :: forall (p :: k) (m :: Multiplicity).
MP1 m f p %m -> Rep1 (MP1 m f) p
from1 MP1 m f p
y = MP1 m f p %1 -> Rep1 (MP1 m f) p
forall (a :: k). MP1 m f a %1 -> Rep1 (MP1 m f) a
from1' MP1 m f p
y
    where
      from1' :: MP1 m f a %1 -> Rep1 (MP1 m f) a
      from1' :: forall (a :: k). MP1 m f a %1 -> Rep1 (MP1 m f) a
from1' (MP1 f a
x) = M1
  C
  ('MetaCons "MP1" 'PrefixI 'False)
  (M1
     S
     ('MetaSel
        'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy)
     (MP1 m (Par1 :.: f)))
  a
%m -> M1
        D
        ('MetaData
           "MP1"
           "Generics.Linear.Class"
           "linear-generics-0.1.0.1-inplace"
           'False)
        (M1
           C
           ('MetaCons "MP1" 'PrefixI 'False)
           (M1
              S
              ('MetaSel
                 'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy)
              (MP1 m (Par1 :.: f))))
        a
forall k i (c :: Meta) (f :: k -> *) (p :: k). f p -> M1 i c f p
M1 (M1
  S
  ('MetaSel
     'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy)
  (MP1 m (Par1 :.: f))
  a
%m -> M1
        C
        ('MetaCons "MP1" 'PrefixI 'False)
        (M1
           S
           ('MetaSel
              'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy)
           (MP1 m (Par1 :.: f)))
        a
forall k i (c :: Meta) (f :: k -> *) (p :: k). f p -> M1 i c f p
M1 (MP1 m (Par1 :.: f) a
%m -> M1
        S
        ('MetaSel
           'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy)
        (MP1 m (Par1 :.: f))
        a
forall k i (c :: Meta) (f :: k -> *) (p :: k). f p -> M1 i c f p
M1 ((:.:) Par1 f a %m -> MP1 m (Par1 :.: f) a
forall {k} (f :: k -> *) (a :: k) (m :: Multiplicity).
f a %m -> MP1 m f a
MP1 (Par1 (f a) %m -> (:.:) Par1 f a
forall k2 k1 (f :: k2 -> *) (g :: k1 -> k2) (x :: k1).
f (g x) -> (:.:) f g x
Comp1 (f a %m -> Par1 (f a)
forall p. p -> Par1 p
Par1 f a
x)))))
  to1 :: forall (p :: k) (m :: Multiplicity).
Rep1 (MP1 m f) p %m -> MP1 m f p
to1 Rep1 (MP1 m f) p
y = Rep1 (MP1 m f) p %1 -> MP1 m f p
forall (a :: k). Rep1 (MP1 m f) a %1 -> MP1 m f a
to1' Rep1 (MP1 m f) p
y
    where
      to1' :: Rep1 (MP1 m f) a %1 -> MP1 m f a
      to1' :: forall (a :: k). Rep1 (MP1 m f) a %1 -> MP1 m f a
to1' (M1 (M1 (M1 (MP1 (Comp1 (Par1 f a
x)))))) = f a %m -> MP1 m f a
forall {k} (f :: k -> *) (a :: k) (m :: Multiplicity).
f a %m -> MP1 m f a
MP1 f a
x