{-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE PolyKinds #-} {-# LANGUAGE QuantifiedConstraints #-} {-# LANGUAGE RankNTypes #-} {-# LANGUAGE TypeOperators #-} {-# OPTIONS_GHC -Wall -Wno-name-shadowing #-} module Data.IFunctor.IIdentity ( IIdentity (IIdentity, runIIdentity) ) where import Data.Data (Data) import Data.Function (on) import Data.IComonad (IComonad (..)) import Data.IFunctor (IFunctor (..)) import Data.IFunctor.Classes import Data.IMonad (IMonad (..)) import Data.ITraversable (ITraversable (..)) import Data.Typeable (Typeable) import GHC.Generics (Generic, Generic1) import Singlethongs (SingI) import Text.Read data IIdentity f ix = IIdentity { IIdentity f ix -> f ix runIIdentity :: f ix } deriving (Typeable, Typeable (IIdentity f ix) DataType Constr Typeable (IIdentity f ix) => (forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> IIdentity f ix -> c (IIdentity f ix)) -> (forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (IIdentity f ix)) -> (IIdentity f ix -> Constr) -> (IIdentity f ix -> DataType) -> (forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (IIdentity f ix))) -> (forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (IIdentity f ix))) -> ((forall b. Data b => b -> b) -> IIdentity f ix -> IIdentity f ix) -> (forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> IIdentity f ix -> r) -> (forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> IIdentity f ix -> r) -> (forall u. (forall d. Data d => d -> u) -> IIdentity f ix -> [u]) -> (forall u. Int -> (forall d. Data d => d -> u) -> IIdentity f ix -> u) -> (forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> IIdentity f ix -> m (IIdentity f ix)) -> (forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> IIdentity f ix -> m (IIdentity f ix)) -> (forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> IIdentity f ix -> m (IIdentity f ix)) -> Data (IIdentity f ix) IIdentity f ix -> DataType IIdentity f ix -> Constr (forall b. Data b => b -> b) -> IIdentity f ix -> IIdentity f ix (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> IIdentity f ix -> c (IIdentity f ix) (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (IIdentity f ix) 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) -> IIdentity f ix -> u forall u. (forall d. Data d => d -> u) -> IIdentity f ix -> [u] forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> IIdentity f ix -> r forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> IIdentity f ix -> r forall k (f :: k -> *) (ix :: k). (Typeable ix, Typeable f, Typeable k, Data (f ix)) => Typeable (IIdentity f ix) forall k (f :: k -> *) (ix :: k). (Typeable ix, Typeable f, Typeable k, Data (f ix)) => IIdentity f ix -> DataType forall k (f :: k -> *) (ix :: k). (Typeable ix, Typeable f, Typeable k, Data (f ix)) => IIdentity f ix -> Constr forall k (f :: k -> *) (ix :: k). (Typeable ix, Typeable f, Typeable k, Data (f ix)) => (forall b. Data b => b -> b) -> IIdentity f ix -> IIdentity f ix forall k (f :: k -> *) (ix :: k) u. (Typeable ix, Typeable f, Typeable k, Data (f ix)) => Int -> (forall d. Data d => d -> u) -> IIdentity f ix -> u forall k (f :: k -> *) (ix :: k) u. (Typeable ix, Typeable f, Typeable k, Data (f ix)) => (forall d. Data d => d -> u) -> IIdentity f ix -> [u] forall k (f :: k -> *) (ix :: k) r r'. (Typeable ix, Typeable f, Typeable k, Data (f ix)) => (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> IIdentity f ix -> r forall k (f :: k -> *) (ix :: k) r r'. (Typeable ix, Typeable f, Typeable k, Data (f ix)) => (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> IIdentity f ix -> r forall k (f :: k -> *) (ix :: k) (m :: * -> *). (Typeable ix, Typeable f, Typeable k, Data (f ix), Monad m) => (forall d. Data d => d -> m d) -> IIdentity f ix -> m (IIdentity f ix) forall k (f :: k -> *) (ix :: k) (m :: * -> *). (Typeable ix, Typeable f, Typeable k, Data (f ix), MonadPlus m) => (forall d. Data d => d -> m d) -> IIdentity f ix -> m (IIdentity f ix) forall k (f :: k -> *) (ix :: k) (c :: * -> *). (Typeable ix, Typeable f, Typeable k, Data (f ix)) => (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (IIdentity f ix) forall k (f :: k -> *) (ix :: k) (c :: * -> *). (Typeable ix, Typeable f, Typeable k, Data (f ix)) => (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> IIdentity f ix -> c (IIdentity f ix) forall k (f :: k -> *) (ix :: k) (t :: * -> *) (c :: * -> *). (Typeable ix, Typeable f, Typeable k, Data (f ix), Typeable t) => (forall d. Data d => c (t d)) -> Maybe (c (IIdentity f ix)) forall k (f :: k -> *) (ix :: k) (t :: * -> * -> *) (c :: * -> *). (Typeable ix, Typeable f, Typeable k, Data (f ix), Typeable t) => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (IIdentity f ix)) forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> IIdentity f ix -> m (IIdentity f ix) forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> IIdentity f ix -> m (IIdentity f ix) forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (IIdentity f ix) forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> IIdentity f ix -> c (IIdentity f ix) forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (IIdentity f ix)) forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (IIdentity f ix)) $cIIdentity :: Constr $tIIdentity :: DataType gmapMo :: (forall d. Data d => d -> m d) -> IIdentity f ix -> m (IIdentity f ix) $cgmapMo :: forall k (f :: k -> *) (ix :: k) (m :: * -> *). (Typeable ix, Typeable f, Typeable k, Data (f ix), MonadPlus m) => (forall d. Data d => d -> m d) -> IIdentity f ix -> m (IIdentity f ix) gmapMp :: (forall d. Data d => d -> m d) -> IIdentity f ix -> m (IIdentity f ix) $cgmapMp :: forall k (f :: k -> *) (ix :: k) (m :: * -> *). (Typeable ix, Typeable f, Typeable k, Data (f ix), MonadPlus m) => (forall d. Data d => d -> m d) -> IIdentity f ix -> m (IIdentity f ix) gmapM :: (forall d. Data d => d -> m d) -> IIdentity f ix -> m (IIdentity f ix) $cgmapM :: forall k (f :: k -> *) (ix :: k) (m :: * -> *). (Typeable ix, Typeable f, Typeable k, Data (f ix), Monad m) => (forall d. Data d => d -> m d) -> IIdentity f ix -> m (IIdentity f ix) gmapQi :: Int -> (forall d. Data d => d -> u) -> IIdentity f ix -> u $cgmapQi :: forall k (f :: k -> *) (ix :: k) u. (Typeable ix, Typeable f, Typeable k, Data (f ix)) => Int -> (forall d. Data d => d -> u) -> IIdentity f ix -> u gmapQ :: (forall d. Data d => d -> u) -> IIdentity f ix -> [u] $cgmapQ :: forall k (f :: k -> *) (ix :: k) u. (Typeable ix, Typeable f, Typeable k, Data (f ix)) => (forall d. Data d => d -> u) -> IIdentity f ix -> [u] gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> IIdentity f ix -> r $cgmapQr :: forall k (f :: k -> *) (ix :: k) r r'. (Typeable ix, Typeable f, Typeable k, Data (f ix)) => (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> IIdentity f ix -> r gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> IIdentity f ix -> r $cgmapQl :: forall k (f :: k -> *) (ix :: k) r r'. (Typeable ix, Typeable f, Typeable k, Data (f ix)) => (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> IIdentity f ix -> r gmapT :: (forall b. Data b => b -> b) -> IIdentity f ix -> IIdentity f ix $cgmapT :: forall k (f :: k -> *) (ix :: k). (Typeable ix, Typeable f, Typeable k, Data (f ix)) => (forall b. Data b => b -> b) -> IIdentity f ix -> IIdentity f ix dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (IIdentity f ix)) $cdataCast2 :: forall k (f :: k -> *) (ix :: k) (t :: * -> * -> *) (c :: * -> *). (Typeable ix, Typeable f, Typeable k, Data (f ix), Typeable t) => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (IIdentity f ix)) dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c (IIdentity f ix)) $cdataCast1 :: forall k (f :: k -> *) (ix :: k) (t :: * -> *) (c :: * -> *). (Typeable ix, Typeable f, Typeable k, Data (f ix), Typeable t) => (forall d. Data d => c (t d)) -> Maybe (c (IIdentity f ix)) dataTypeOf :: IIdentity f ix -> DataType $cdataTypeOf :: forall k (f :: k -> *) (ix :: k). (Typeable ix, Typeable f, Typeable k, Data (f ix)) => IIdentity f ix -> DataType toConstr :: IIdentity f ix -> Constr $ctoConstr :: forall k (f :: k -> *) (ix :: k). (Typeable ix, Typeable f, Typeable k, Data (f ix)) => IIdentity f ix -> Constr gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (IIdentity f ix) $cgunfold :: forall k (f :: k -> *) (ix :: k) (c :: * -> *). (Typeable ix, Typeable f, Typeable k, Data (f ix)) => (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (IIdentity f ix) gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> IIdentity f ix -> c (IIdentity f ix) $cgfoldl :: forall k (f :: k -> *) (ix :: k) (c :: * -> *). (Typeable ix, Typeable f, Typeable k, Data (f ix)) => (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> IIdentity f ix -> c (IIdentity f ix) $cp1Data :: forall k (f :: k -> *) (ix :: k). (Typeable ix, Typeable f, Typeable k, Data (f ix)) => Typeable (IIdentity f ix) Data, (forall x. IIdentity f ix -> Rep (IIdentity f ix) x) -> (forall x. Rep (IIdentity f ix) x -> IIdentity f ix) -> Generic (IIdentity f ix) forall x. Rep (IIdentity f ix) x -> IIdentity f ix forall x. IIdentity f ix -> Rep (IIdentity f ix) x forall a. (forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a forall k (f :: k -> *) (ix :: k) x. Rep (IIdentity f ix) x -> IIdentity f ix forall k (f :: k -> *) (ix :: k) x. IIdentity f ix -> Rep (IIdentity f ix) x $cto :: forall k (f :: k -> *) (ix :: k) x. Rep (IIdentity f ix) x -> IIdentity f ix $cfrom :: forall k (f :: k -> *) (ix :: k) x. IIdentity f ix -> Rep (IIdentity f ix) x Generic, (forall (a :: k). IIdentity f a -> Rep1 (IIdentity f) a) -> (forall (a :: k). Rep1 (IIdentity f) a -> IIdentity f a) -> Generic1 (IIdentity f) forall (a :: k). Rep1 (IIdentity f) a -> IIdentity f a forall (a :: k). IIdentity f a -> Rep1 (IIdentity f) a forall k (f :: k -> *). (forall (a :: k). f a -> Rep1 f a) -> (forall (a :: k). Rep1 f a -> f a) -> Generic1 f forall k (f :: k -> *) (a :: k). Rep1 (IIdentity f) a -> IIdentity f a forall k (f :: k -> *) (a :: k). IIdentity f a -> Rep1 (IIdentity f) a $cto1 :: forall k (f :: k -> *) (a :: k). Rep1 (IIdentity f) a -> IIdentity f a $cfrom1 :: forall k (f :: k -> *) (a :: k). IIdentity f a -> Rep1 (IIdentity f) a Generic1) instance IFunctor IIdentity where imap :: (a ~~> b) -> IIdentity a ~~> IIdentity b imap f :: a ~~> b f = b ix -> IIdentity b ix forall k (f :: k -> *) (ix :: k). f ix -> IIdentity f ix IIdentity (b ix -> IIdentity b ix) -> (IIdentity a ix -> b ix) -> IIdentity a ix -> IIdentity b ix forall b c a. (b -> c) -> (a -> b) -> a -> c . a ix -> b ix a ~~> b f (a ix -> b ix) -> (IIdentity a ix -> a ix) -> IIdentity a ix -> b ix forall b c a. (b -> c) -> (a -> b) -> a -> c . IIdentity a ix -> a ix forall k (f :: k -> *) (ix :: k). IIdentity f ix -> f ix runIIdentity instance IMonad IIdentity where ipure :: a ix -> IIdentity a ix ipure = a ix -> IIdentity a ix forall k (f :: k -> *) (ix :: k). f ix -> IIdentity f ix IIdentity ijoin :: IIdentity (IIdentity a) ix -> IIdentity a ix ijoin = IIdentity (IIdentity a) ix -> IIdentity a ix forall k (f :: k -> *) (ix :: k). IIdentity f ix -> f ix runIIdentity instance IComonad IIdentity where iextract :: IIdentity a ix -> a ix iextract = IIdentity a ix -> a ix forall k (f :: k -> *) (ix :: k). IIdentity f ix -> f ix runIIdentity iduplicate :: IIdentity a ix -> IIdentity (IIdentity a) ix iduplicate = IIdentity a ix -> IIdentity (IIdentity a) ix forall k (f :: k -> *) (ix :: k). f ix -> IIdentity f ix IIdentity instance ITraversable IIdentity where itraverse :: (forall (ix :: k). SingI ix => a ix -> m (b ix)) -> IIdentity a ix -> m (IIdentity b ix) itraverse f :: forall (ix :: k). SingI ix => a ix -> m (b ix) f = (b ix -> IIdentity b ix) -> m (b ix) -> m (IIdentity b ix) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap b ix -> IIdentity b ix forall k (f :: k -> *) (ix :: k). f ix -> IIdentity f ix IIdentity (m (b ix) -> m (IIdentity b ix)) -> (IIdentity a ix -> m (b ix)) -> IIdentity a ix -> m (IIdentity b ix) forall b c a. (b -> c) -> (a -> b) -> a -> c . a ix -> m (b ix) forall (ix :: k). SingI ix => a ix -> m (b ix) f (a ix -> m (b ix)) -> (IIdentity a ix -> a ix) -> IIdentity a ix -> m (b ix) forall b c a. (b -> c) -> (a -> b) -> a -> c . IIdentity a ix -> a ix forall k (f :: k -> *) (ix :: k). IIdentity f ix -> f ix runIIdentity instance IShow IIdentity where ishowsPrec :: (forall (ix :: k). SingI ix => Int -> a ix -> ShowS) -> Int -> IIdentity a ix -> ShowS ishowsPrec sp :: forall (ix :: k). SingI ix => Int -> a ix -> ShowS sp p :: Int p (IIdentity x :: a ix x) = Bool -> ShowS -> ShowS showParen (Int p Int -> Int -> Bool forall a. Ord a => a -> a -> Bool > 10) (ShowS -> ShowS) -> ShowS -> ShowS forall a b. (a -> b) -> a -> b $ String -> ShowS showString "IIdentity " ShowS -> ShowS -> ShowS forall b c a. (b -> c) -> (a -> b) -> a -> c . Int -> a ix -> ShowS forall (ix :: k). SingI ix => Int -> a ix -> ShowS sp Int p a ix x instance IRead IIdentity where ireadPrec :: (forall (ix :: k). SingI ix => ReadPrec (a ix)) -> ReadPrec (IIdentity a ix) ireadPrec rp :: forall (ix :: k). SingI ix => ReadPrec (a ix) rp = ReadPrec (IIdentity a ix) -> ReadPrec (IIdentity a ix) forall a. ReadPrec a -> ReadPrec a parens (ReadPrec (IIdentity a ix) -> ReadPrec (IIdentity a ix)) -> ReadPrec (IIdentity a ix) -> ReadPrec (IIdentity a ix) forall a b. (a -> b) -> a -> b $ Int -> ReadPrec (IIdentity a ix) -> ReadPrec (IIdentity a ix) forall a. Int -> ReadPrec a -> ReadPrec a prec 10 (ReadPrec (IIdentity a ix) -> ReadPrec (IIdentity a ix)) -> ReadPrec (IIdentity a ix) -> ReadPrec (IIdentity a ix) forall a b. (a -> b) -> a -> b $ do Ident "IIdentity" <- ReadPrec Lexeme lexP a ix x <- ReadPrec (a ix) -> ReadPrec (a ix) forall a. ReadPrec a -> ReadPrec a step ReadPrec (a ix) forall (ix :: k). SingI ix => ReadPrec (a ix) rp IIdentity a ix -> ReadPrec (IIdentity a ix) forall (f :: * -> *) a. Applicative f => a -> f a pure (IIdentity a ix -> ReadPrec (IIdentity a ix)) -> IIdentity a ix -> ReadPrec (IIdentity a ix) forall a b. (a -> b) -> a -> b $ a ix -> IIdentity a ix forall k (f :: k -> *) (ix :: k). f ix -> IIdentity f ix IIdentity a ix x instance IEq IIdentity where ieq :: (forall (ix :: k). SingI ix => a ix -> a ix -> Bool) -> IIdentity a ix -> IIdentity a ix -> Bool ieq eq :: forall (ix :: k). SingI ix => a ix -> a ix -> Bool eq = a ix -> a ix -> Bool forall (ix :: k). SingI ix => a ix -> a ix -> Bool eq (a ix -> a ix -> Bool) -> (IIdentity a ix -> a ix) -> IIdentity a ix -> IIdentity a ix -> Bool forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c `on` IIdentity a ix -> a ix forall k (f :: k -> *) (ix :: k). IIdentity f ix -> f ix runIIdentity instance IOrd IIdentity where icompare :: (forall (ix :: k). SingI ix => a ix -> a ix -> Ordering) -> IIdentity a ix -> IIdentity a ix -> Ordering icompare comp :: forall (ix :: k). SingI ix => a ix -> a ix -> Ordering comp = a ix -> a ix -> Ordering forall (ix :: k). SingI ix => a ix -> a ix -> Ordering comp (a ix -> a ix -> Ordering) -> (IIdentity a ix -> a ix) -> IIdentity a ix -> IIdentity a ix -> Ordering forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c `on` IIdentity a ix -> a ix forall k (f :: k -> *) (ix :: k). IIdentity f ix -> f ix runIIdentity instance (IShow2 f, SingI ix) => Show (IIdentity f ix) where showsPrec :: Int -> IIdentity f ix -> ShowS showsPrec = Int -> IIdentity f ix -> ShowS forall k1 k2 (f :: (k1 -> *) -> k2 -> *) (a :: k1 -> *) (ix :: k2). (IShow f, IShow2 a, SingI ix) => Int -> f a ix -> ShowS ishowsPrec1 instance (IRead2 f, SingI ix) => Read (IIdentity f ix) where readPrec :: ReadPrec (IIdentity f ix) readPrec = ReadPrec (IIdentity f ix) forall k1 k2 (f :: (k1 -> *) -> k2 -> *) (a :: k1 -> *) (ix :: k2). (IRead f, IRead2 a, SingI ix) => ReadPrec (f a ix) ireadPrec1 instance (IEq2 f, SingI ix) => Eq (IIdentity f ix) where == :: IIdentity f ix -> IIdentity f ix -> Bool (==) = IIdentity f ix -> IIdentity f ix -> Bool forall k1 k2 (f :: (k1 -> *) -> k2 -> *) (a :: k1 -> *) (ix :: k2). (IEq f, IEq2 a, SingI ix) => f a ix -> f a ix -> Bool ieq1 instance (IOrd2 f, SingI ix) => Ord (IIdentity f ix) where compare :: IIdentity f ix -> IIdentity f ix -> Ordering compare = IIdentity f ix -> IIdentity f ix -> Ordering forall k1 k2 (f :: (k1 -> *) -> k2 -> *) (a :: k1 -> *) (ix :: k2). (IOrd f, IOrd2 a, SingI ix) => f a ix -> f a ix -> Ordering icompare1