(original) (raw)
{-# LANGUAGE CPP #-} {-# LANGUAGE DataKinds #-} {-# LANGUAGE DeriveFunctor #-} {-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE EmptyDataDeriving #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE GeneralizedNewtypeDeriving #-} {-# LANGUAGE MagicHash #-} {-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE PolyKinds #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE StandaloneDeriving #-} {-# LANGUAGE Trustworthy #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeOperators #-} {-# LANGUAGE UndecidableInstances #-}
module GHC.Generics (
#if 0
#endif
#if 0
#endif
#if 0
#endif
[V1](GHC.Generics.html#V1), [U1](GHC.Generics.html#U1)(..), [Par1](GHC.Generics.html#Par1)(..), [Rec1](GHC.Generics.html#Rec1)(..), [K1](GHC.Generics.html#K1)(..), [M1](GHC.Generics.html#M1)(..), (:+:)(..), (:*:)(..), (:.:)(..)
, URec(..) , type UAddr, type UChar, type UDouble , type UFloat, type UInt, type UWord
, Rec0, R , D1, C1, S1, D, C, S
, Datatype(..), Constructor(..), Selector(..) , Fixity(..), FixityI(..), Associativity(..), prec , SourceUnpackedness(..), SourceStrictness(..), DecidedStrictness(..) , Meta(..)
) where
import Data.Either ( Either (..) ) import Data.Maybe ( Maybe(..), fromMaybe ) import Data.Ord ( Down(..) ) import GHC.Num.Integer ( Integer, integerToInt ) import GHC.Prim ( Addr#, Char#, Double#, Float#, Int#, Word# ) import GHC.Ptr ( Ptr ) import GHC.Types
import GHC.Ix ( Ix ) import GHC.Base ( Alternative(..), Applicative(..), Functor(..) , Monad(..), MonadPlus(..), NonEmpty(..), String, coerce , Semigroup(..), Monoid(..) ) import GHC.Classes ( Eq(..), Ord(..) ) import GHC.Enum ( Bounded, Enum ) import GHC.Read ( Read(..) ) import GHC.Show ( Show(..), showString ) import GHC.Stack.Types ( SrcLoc(..) ) import GHC.Tuple (Solo (..)) import GHC.Unicode ( GeneralCategory(..) ) import GHC.Fingerprint.Type ( Fingerprint(..) )
import Data.Proxy ( Proxy(..) ) import GHC.TypeLits ( KnownSymbol, KnownNat, Nat, symbolVal, natVal )
data V1 (p :: k)
deriving ( V1 p -> V1 p -> Bool
(V1 p -> V1 p -> Bool) -> (V1 p -> V1 p -> Bool) -> Eq (V1 p)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall k (p :: k). V1 p -> V1 p -> Bool
/= :: V1 p -> V1 p -> Bool
$c/= :: forall k (p :: k). V1 p -> V1 p -> Bool
== :: V1 p -> V1 p -> Bool
$c== :: forall k (p :: k). V1 p -> V1 p -> Bool
Eq
, Eq (V1 p)
Eq (V1 p)
-> (V1 p -> V1 p -> Ordering)
-> (V1 p -> V1 p -> Bool)
-> (V1 p -> V1 p -> Bool)
-> (V1 p -> V1 p -> Bool)
-> (V1 p -> V1 p -> Bool)
-> (V1 p -> V1 p -> V1 p)
-> (V1 p -> V1 p -> V1 p)
-> Ord (V1 p)
V1 p -> V1 p -> Bool
V1 p -> V1 p -> Ordering
V1 p -> V1 p -> V1 p
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 k (p :: k). Eq (V1 p)
forall k (p :: k). V1 p -> V1 p -> Bool
forall k (p :: k). V1 p -> V1 p -> Ordering
forall k (p :: k). V1 p -> V1 p -> V1 p
min :: V1 p -> V1 p -> V1 p
$cmin :: forall k (p :: k). V1 p -> V1 p -> V1 p
max :: V1 p -> V1 p -> V1 p
$cmax :: forall k (p :: k). V1 p -> V1 p -> V1 p
= :: V1 p -> V1 p -> Bool $c>= :: forall k (p :: k). V1 p -> V1 p -> Bool :: V1 p -> V1 p -> Bool $c> :: forall k (p :: k). V1 p -> V1 p -> Bool <= :: V1 p -> V1 p -> Bool $c<= :: forall k (p :: k). V1 p -> V1 p -> Bool < :: V1 p -> V1 p -> Bool $c< :: forall k (p :: k). V1 p -> V1 p -> Bool compare :: V1 p -> V1 p -> Ordering $ccompare :: forall k (p :: k). V1 p -> V1 p -> Ordering Ord
, ReadPrec [V1 p] ReadPrec (V1 p) Int -> ReadS (V1 p) ReadS [V1 p] (Int -> ReadS (V1 p)) -> ReadS [V1 p] -> ReadPrec (V1 p) -> ReadPrec [V1 p] -> Read (V1 p) forall a. (Int -> ReadS a) -> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a forall k (p :: k). ReadPrec [V1 p] forall k (p :: k). ReadPrec (V1 p) forall k (p :: k). Int -> ReadS (V1 p) forall k (p :: k). ReadS [V1 p] readListPrec :: ReadPrec [V1 p] $creadListPrec :: forall k (p :: k). ReadPrec [V1 p] readPrec :: ReadPrec (V1 p) $creadPrec :: forall k (p :: k). ReadPrec (V1 p) readList :: ReadS [V1 p] $creadList :: forall k (p :: k). ReadS [V1 p] readsPrec :: Int -> ReadS (V1 p) $creadsPrec :: forall k (p :: k). Int -> ReadS (V1 p) Read
, Int -> V1 p -> ShowS [V1 p] -> ShowS V1 p -> String (Int -> V1 p -> ShowS) -> (V1 p -> String) -> ([V1 p] -> ShowS) -> Show (V1 p) forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a forall k (p :: k). Int -> V1 p -> ShowS forall k (p :: k). [V1 p] -> ShowS forall k (p :: k). V1 p -> String showList :: [V1 p] -> ShowS $cshowList :: forall k (p :: k). [V1 p] -> ShowS show :: V1 p -> String $cshow :: forall k (p :: k). V1 p -> String showsPrec :: Int -> V1 p -> ShowS $cshowsPrec :: forall k (p :: k). Int -> V1 p -> ShowS Show
, (forall a b. (a -> b) -> V1 a -> V1 b) -> (forall a b. a -> V1 b -> V1 a) -> Functor V1 forall a b. a -> V1 b -> V1 a forall a b. (a -> b) -> V1 a -> V1 b forall (f :: * -> *). (forall a b. (a -> b) -> f a -> f b) -> (forall a b. a -> f b -> f a) -> Functor f <$ :: forall a b. a -> V1 b -> V1 a c<c<c< :: forall a b. a -> V1 b -> V1 a fmap :: forall a b. (a -> b) -> V1 a -> V1 b $cfmap :: forall a b. (a -> b) -> V1 a -> V1 b Functor
, (forall x. V1 p -> Rep (V1 p) x) -> (forall x. Rep (V1 p) x -> V1 p) -> Generic (V1 p) forall x. V1 p -> Rep (V1 p) x forall x. Rep (V1 p) x -> V1 p forall a. (forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a forall k (p :: k) x. V1 p -> Rep (V1 p) x forall k (p :: k) x. Rep (V1 p) x -> V1 p $cto :: forall k (p :: k) x. Rep (V1 p) x -> V1 p $cfrom :: forall k (p :: k) x. V1 p -> Rep (V1 p) x Generic
, (forall (a :: k). V1 a -> Rep1 V1 a) -> (forall (a :: k). Rep1 V1 a -> V1 a) -> Generic1 V1 forall (a :: k). V1 a -> Rep1 V1 a forall (a :: k). Rep1 V1 a -> V1 a forall k (a :: k). V1 a -> Rep1 V1 a forall k (a :: k). Rep1 V1 a -> V1 a forall k (f :: k -> *). (forall (a :: k). f a -> Rep1 f a) -> (forall (a :: k). Rep1 f a -> f a) -> Generic1 f $cto1 :: forall k (a :: k). Rep1 V1 a -> V1 a $cfrom1 :: forall k (a :: k). V1 a -> Rep1 V1 a Generic1 )
instance Semigroup (V1 p) where V1 p v <> :: V1 p -> V1 p -> V1 p <> V1 p _ = V1 p v
data U1 (p :: k) = U1
deriving ( (forall x. U1 p -> Rep (U1 p) x)
-> (forall x. Rep (U1 p) x -> U1 p) -> Generic (U1 p)
forall x. U1 p -> Rep (U1 p) x
forall x. Rep (U1 p) x -> U1 p
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall k (p :: k) x. U1 p -> Rep (U1 p) x
forall k (p :: k) x. Rep (U1 p) x -> U1 p
$cto :: forall k (p :: k) x. Rep (U1 p) x -> U1 p
$cfrom :: forall k (p :: k) x. U1 p -> Rep (U1 p) x
Generic
, (forall (a :: k). U1 a -> Rep1 U1 a)
-> (forall (a :: k). Rep1 U1 a -> U1 a) -> Generic1 U1
forall (a :: k). U1 a -> Rep1 U1 a
forall (a :: k). Rep1 U1 a -> U1 a
forall k (a :: k). U1 a -> Rep1 U1 a
forall k (a :: k). Rep1 U1 a -> U1 a
forall k (f :: k -> *).
(forall (a :: k). f a -> Rep1 f a)
-> (forall (a :: k). Rep1 f a -> f a) -> Generic1 f
$cto1 :: forall k (a :: k). Rep1 U1 a -> U1 a
$cfrom1 :: forall k (a :: k). U1 a -> Rep1 U1 a
Generic1
)
instance Eq (U1 p) where U1 p _ == :: U1 p -> U1 p -> Bool == U1 p _ = Bool True
instance Ord (U1 p) where compare :: U1 p -> U1 p -> Ordering compare U1 p _ U1 p _ = Ordering EQ
instance Show (U1 p) where showsPrec :: Int -> U1 p -> ShowS showsPrec Int _ U1 p _ = String -> ShowS showString String "U1"
instance Functor U1 where fmap :: forall a b. (a -> b) -> U1 a -> U1 b fmap a -> b _ U1 a _ = U1 b forall k (p :: k). U1 p U1
instance Applicative U1 where pure :: forall a. a -> U1 a pure a _ = U1 a forall k (p :: k). U1 p U1 U1 (a -> b) _ <*> :: forall a b. U1 (a -> b) -> U1 a -> U1 b <*> U1 a _ = U1 b forall k (p :: k). U1 p U1 liftA2 :: forall a b c. (a -> b -> c) -> U1 a -> U1 b -> U1 c liftA2 a -> b -> c _ U1 a _ U1 b _ = U1 c forall k (p :: k). U1 p U1
instance Alternative U1 where empty :: forall a. U1 a empty = U1 a forall k (p :: k). U1 p U1 U1 a _ <|> :: forall a. U1 a -> U1 a -> U1 a <|> U1 a _ = U1 a forall k (p :: k). U1 p U1
instance Monad U1 where U1 a _ >>= :: forall a b. U1 a -> (a -> U1 b) -> U1 b >>= a -> U1 b _ = U1 b forall k (p :: k). U1 p U1
instance Semigroup (U1 p) where U1 p _ <> :: U1 p -> U1 p -> U1 p <> U1 p _ = U1 p forall k (p :: k). U1 p U1
instance Monoid (U1 p) where mempty :: U1 p mempty = U1 p forall k (p :: k). U1 p U1
newtype Par1 p = Par1 { forall p. Par1 p -> p
unPar1 :: p }
deriving ( Par1 p -> Par1 p -> Bool
(Par1 p -> Par1 p -> Bool)
-> (Par1 p -> Par1 p -> Bool) -> Eq (Par1 p)
forall p. Eq p => Par1 p -> Par1 p -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Par1 p -> Par1 p -> Bool
$c/= :: forall p. Eq p => Par1 p -> Par1 p -> Bool
== :: Par1 p -> Par1 p -> Bool
$c== :: forall p. Eq p => Par1 p -> Par1 p -> Bool
Eq
, Eq (Par1 p)
Eq (Par1 p)
-> (Par1 p -> Par1 p -> Ordering)
-> (Par1 p -> Par1 p -> Bool)
-> (Par1 p -> Par1 p -> Bool)
-> (Par1 p -> Par1 p -> Bool)
-> (Par1 p -> Par1 p -> Bool)
-> (Par1 p -> Par1 p -> Par1 p)
-> (Par1 p -> Par1 p -> Par1 p)
-> Ord (Par1 p)
Par1 p -> Par1 p -> Bool
Par1 p -> Par1 p -> Ordering
Par1 p -> Par1 p -> Par1 p
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 {p}. Ord p => Eq (Par1 p)
forall p. Ord p => Par1 p -> Par1 p -> Bool
forall p. Ord p => Par1 p -> Par1 p -> Ordering
forall p. Ord p => Par1 p -> Par1 p -> Par1 p
min :: Par1 p -> Par1 p -> Par1 p
$cmin :: forall p. Ord p => Par1 p -> Par1 p -> Par1 p
max :: Par1 p -> Par1 p -> Par1 p
$cmax :: forall p. Ord p => Par1 p -> Par1 p -> Par1 p
= :: Par1 p -> Par1 p -> Bool $c>= :: forall p. Ord p => Par1 p -> Par1 p -> Bool :: Par1 p -> Par1 p -> Bool $c> :: forall p. Ord p => Par1 p -> Par1 p -> Bool <= :: Par1 p -> Par1 p -> Bool $c<= :: forall p. Ord p => Par1 p -> Par1 p -> Bool < :: Par1 p -> Par1 p -> Bool $c< :: forall p. Ord p => Par1 p -> Par1 p -> Bool compare :: Par1 p -> Par1 p -> Ordering $ccompare :: forall p. Ord p => Par1 p -> Par1 p -> Ordering Ord
, ReadPrec [Par1 p] ReadPrec (Par1 p) Int -> ReadS (Par1 p) ReadS [Par1 p] (Int -> ReadS (Par1 p)) -> ReadS [Par1 p] -> ReadPrec (Par1 p) -> ReadPrec [Par1 p] -> Read (Par1 p) forall p. Read p => ReadPrec [Par1 p] forall p. Read p => ReadPrec (Par1 p) forall p. Read p => Int -> ReadS (Par1 p) forall p. Read p => ReadS [Par1 p] forall a. (Int -> ReadS a) -> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a readListPrec :: ReadPrec [Par1 p] $creadListPrec :: forall p. Read p => ReadPrec [Par1 p] readPrec :: ReadPrec (Par1 p) $creadPrec :: forall p. Read p => ReadPrec (Par1 p) readList :: ReadS [Par1 p] $creadList :: forall p. Read p => ReadS [Par1 p] readsPrec :: Int -> ReadS (Par1 p) $creadsPrec :: forall p. Read p => Int -> ReadS (Par1 p) Read
, Int -> Par1 p -> ShowS [Par1 p] -> ShowS Par1 p -> String (Int -> Par1 p -> ShowS) -> (Par1 p -> String) -> ([Par1 p] -> ShowS) -> Show (Par1 p) forall p. Show p => Int -> Par1 p -> ShowS forall p. Show p => [Par1 p] -> ShowS forall p. Show p => Par1 p -> String forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [Par1 p] -> ShowS $cshowList :: forall p. Show p => [Par1 p] -> ShowS show :: Par1 p -> String $cshow :: forall p. Show p => Par1 p -> String showsPrec :: Int -> Par1 p -> ShowS $cshowsPrec :: forall p. Show p => Int -> Par1 p -> ShowS Show
, (forall a b. (a -> b) -> Par1 a -> Par1 b) -> (forall a b. a -> Par1 b -> Par1 a) -> Functor Par1 forall a b. a -> Par1 b -> Par1 a forall a b. (a -> b) -> Par1 a -> Par1 b forall (f :: * -> *). (forall a b. (a -> b) -> f a -> f b) -> (forall a b. a -> f b -> f a) -> Functor f <$ :: forall a b. a -> Par1 b -> Par1 a c<c<c< :: forall a b. a -> Par1 b -> Par1 a fmap :: forall a b. (a -> b) -> Par1 a -> Par1 b $cfmap :: forall a b. (a -> b) -> Par1 a -> Par1 b Functor
, (forall x. Par1 p -> Rep (Par1 p) x) -> (forall x. Rep (Par1 p) x -> Par1 p) -> Generic (Par1 p) forall x. Par1 p -> Rep (Par1 p) x forall x. Rep (Par1 p) x -> Par1 p forall a. (forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a forall p x. Par1 p -> Rep (Par1 p) x forall p x. Rep (Par1 p) x -> Par1 p $cto :: forall p x. Rep (Par1 p) x -> Par1 p $cfrom :: forall p x. Par1 p -> Rep (Par1 p) x Generic
, (forall a. Par1 a -> Rep1 Par1 a) -> (forall a. Rep1 Par1 a -> Par1 a) -> Generic1 Par1 forall a. Par1 a -> Rep1 Par1 a forall a. Rep1 Par1 a -> Par1 a forall k (f :: k -> *). (forall (a :: k). f a -> Rep1 f a) -> (forall (a :: k). Rep1 f a -> f a) -> Generic1 f $cto1 :: forall a. Rep1 Par1 a -> Par1 a $cfrom1 :: forall a. Par1 a -> Rep1 Par1 a Generic1 )
instance Applicative Par1 where pure :: forall a. a -> Par1 a pure = a -> Par1 a forall a. a -> Par1 a Par1 <*> :: forall a b. Par1 (a -> b) -> Par1 a -> Par1 b (<*>) = Par1 (a -> b) -> Par1 a -> Par1 b coerce liftA2 :: forall a b c. (a -> b -> c) -> Par1 a -> Par1 b -> Par1 c liftA2 = (a -> b -> c) -> Par1 a -> Par1 b -> Par1 c coerce
instance Monad Par1 where Par1 a x >>= :: forall a b. Par1 a -> (a -> Par1 b) -> Par1 b >>= a -> Par1 b f = a -> Par1 b f a x
deriving instance Semigroup p => Semigroup (Par1 p)
deriving instance Monoid p => Monoid (Par1 p)
newtype Rec1 (f :: k -> Type) (p :: k) = Rec1 { forall k (f :: k -> *) (p :: k). Rec1 f p -> f p
unRec1 :: f p }
deriving ( Rec1 f p -> Rec1 f p -> Bool
(Rec1 f p -> Rec1 f p -> Bool)
-> (Rec1 f p -> Rec1 f p -> Bool) -> Eq (Rec1 f p)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall k (f :: k -> *) (p :: k).
Eq (f p) =>
Rec1 f p -> Rec1 f p -> Bool
/= :: Rec1 f p -> Rec1 f p -> Bool
$c/= :: forall k (f :: k -> *) (p :: k).
Eq (f p) =>
Rec1 f p -> Rec1 f p -> Bool
== :: Rec1 f p -> Rec1 f p -> Bool
$c== :: forall k (f :: k -> *) (p :: k).
Eq (f p) =>
Rec1 f p -> Rec1 f p -> Bool
Eq
, Eq (Rec1 f p)
Eq (Rec1 f p)
-> (Rec1 f p -> Rec1 f p -> Ordering)
-> (Rec1 f p -> Rec1 f p -> Bool)
-> (Rec1 f p -> Rec1 f p -> Bool)
-> (Rec1 f p -> Rec1 f p -> Bool)
-> (Rec1 f p -> Rec1 f p -> Bool)
-> (Rec1 f p -> Rec1 f p -> Rec1 f p)
-> (Rec1 f p -> Rec1 f p -> Rec1 f p)
-> Ord (Rec1 f p)
Rec1 f p -> Rec1 f p -> Bool
Rec1 f p -> Rec1 f p -> Ordering
Rec1 f p -> Rec1 f p -> Rec1 f p
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 {k} {f :: k -> *} {p :: k}. Ord (f p) => Eq (Rec1 f p)
forall k (f :: k -> *) (p :: k).
Ord (f p) =>
Rec1 f p -> Rec1 f p -> Bool
forall k (f :: k -> *) (p :: k).
Ord (f p) =>
Rec1 f p -> Rec1 f p -> Ordering
forall k (f :: k -> *) (p :: k).
Ord (f p) =>
Rec1 f p -> Rec1 f p -> Rec1 f p
min :: Rec1 f p -> Rec1 f p -> Rec1 f p
$cmin :: forall k (f :: k -> *) (p :: k).
Ord (f p) =>
Rec1 f p -> Rec1 f p -> Rec1 f p
max :: Rec1 f p -> Rec1 f p -> Rec1 f p
$cmax :: forall k (f :: k -> *) (p :: k).
Ord (f p) =>
Rec1 f p -> Rec1 f p -> Rec1 f p
= :: Rec1 f p -> Rec1 f p -> Bool $c>= :: forall k (f :: k -> *) (p :: k). Ord (f p) => Rec1 f p -> Rec1 f p -> Bool :: Rec1 f p -> Rec1 f p -> Bool $c> :: forall k (f :: k -> *) (p :: k). Ord (f p) => Rec1 f p -> Rec1 f p -> Bool <= :: Rec1 f p -> Rec1 f p -> Bool $c<= :: forall k (f :: k -> *) (p :: k). Ord (f p) => Rec1 f p -> Rec1 f p -> Bool < :: Rec1 f p -> Rec1 f p -> Bool $c< :: forall k (f :: k -> *) (p :: k). Ord (f p) => Rec1 f p -> Rec1 f p -> Bool compare :: Rec1 f p -> Rec1 f p -> Ordering $ccompare :: forall k (f :: k -> *) (p :: k). Ord (f p) => Rec1 f p -> Rec1 f p -> Ordering Ord
, ReadPrec [Rec1 f p] ReadPrec (Rec1 f p) Int -> ReadS (Rec1 f p) ReadS [Rec1 f p] (Int -> ReadS (Rec1 f p)) -> ReadS [Rec1 f p] -> ReadPrec (Rec1 f p) -> ReadPrec [Rec1 f p] -> Read (Rec1 f p) forall a. (Int -> ReadS a) -> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a forall k (f :: k -> *) (p :: k). Read (f p) => ReadPrec [Rec1 f p] forall k (f :: k -> *) (p :: k). Read (f p) => ReadPrec (Rec1 f p) forall k (f :: k -> *) (p :: k). Read (f p) => Int -> ReadS (Rec1 f p) forall k (f :: k -> *) (p :: k). Read (f p) => ReadS [Rec1 f p] readListPrec :: ReadPrec [Rec1 f p] $creadListPrec :: forall k (f :: k -> *) (p :: k). Read (f p) => ReadPrec [Rec1 f p] readPrec :: ReadPrec (Rec1 f p) $creadPrec :: forall k (f :: k -> *) (p :: k). Read (f p) => ReadPrec (Rec1 f p) readList :: ReadS [Rec1 f p] $creadList :: forall k (f :: k -> *) (p :: k). Read (f p) => ReadS [Rec1 f p] readsPrec :: Int -> ReadS (Rec1 f p) $creadsPrec :: forall k (f :: k -> *) (p :: k). Read (f p) => Int -> ReadS (Rec1 f p) Read
, Int -> Rec1 f p -> ShowS [Rec1 f p] -> ShowS Rec1 f p -> String (Int -> Rec1 f p -> ShowS) -> (Rec1 f p -> String) -> ([Rec1 f p] -> ShowS) -> Show (Rec1 f p) forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a forall k (f :: k -> *) (p :: k). Show (f p) => Int -> Rec1 f p -> ShowS forall k (f :: k -> *) (p :: k). Show (f p) => [Rec1 f p] -> ShowS forall k (f :: k -> *) (p :: k). Show (f p) => Rec1 f p -> String showList :: [Rec1 f p] -> ShowS $cshowList :: forall k (f :: k -> *) (p :: k). Show (f p) => [Rec1 f p] -> ShowS show :: Rec1 f p -> String $cshow :: forall k (f :: k -> *) (p :: k). Show (f p) => Rec1 f p -> String showsPrec :: Int -> Rec1 f p -> ShowS $cshowsPrec :: forall k (f :: k -> *) (p :: k). Show (f p) => Int -> Rec1 f p -> ShowS Show
, (forall a b. (a -> b) -> Rec1 f a -> Rec1 f b) -> (forall a b. a -> Rec1 f b -> Rec1 f a) -> Functor (Rec1 f) forall a b. a -> Rec1 f b -> Rec1 f a forall a b. (a -> b) -> Rec1 f a -> Rec1 f b forall (f :: * -> *) a b. Functor f => a -> Rec1 f b -> Rec1 f a forall (f :: * -> *) a b. Functor f => (a -> b) -> Rec1 f a -> Rec1 f b forall (f :: * -> *). (forall a b. (a -> b) -> f a -> f b) -> (forall a b. a -> f b -> f a) -> Functor f <$ :: forall a b. a -> Rec1 f b -> Rec1 f a c<c<c< :: forall (f :: * -> *) a b. Functor f => a -> Rec1 f b -> Rec1 f a fmap :: forall a b. (a -> b) -> Rec1 f a -> Rec1 f b $cfmap :: forall (f :: * -> *) a b. Functor f => (a -> b) -> Rec1 f a -> Rec1 f b Functor
, (forall x. Rec1 f p -> Rep (Rec1 f p) x) -> (forall x. Rep (Rec1 f p) x -> Rec1 f p) -> Generic (Rec1 f p) forall x. Rec1 f p -> Rep (Rec1 f p) x forall x. Rep (Rec1 f p) x -> Rec1 f p forall a. (forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a forall k (f :: k -> *) (p :: k) x. Rec1 f p -> Rep (Rec1 f p) x forall k (f :: k -> *) (p :: k) x. Rep (Rec1 f p) x -> Rec1 f p $cto :: forall k (f :: k -> *) (p :: k) x. Rep (Rec1 f p) x -> Rec1 f p $cfrom :: forall k (f :: k -> *) (p :: k) x. Rec1 f p -> Rep (Rec1 f p) x Generic
, (forall (a :: k). Rec1 f a -> Rep1 (Rec1 f) a) -> (forall (a :: k). Rep1 (Rec1 f) a -> Rec1 f a) -> Generic1 (Rec1 f) forall (a :: k). Rec1 f a -> Rep1 (Rec1 f) a forall (a :: k). Rep1 (Rec1 f) a -> Rec1 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). Rec1 f a -> Rep1 (Rec1 f) a forall k (f :: k -> *) (a :: k). Rep1 (Rec1 f) a -> Rec1 f a $cto1 :: forall k (f :: k -> *) (a :: k). Rep1 (Rec1 f) a -> Rec1 f a $cfrom1 :: forall k (f :: k -> *) (a :: k). Rec1 f a -> Rep1 (Rec1 f) a Generic1 )
deriving instance Applicative f => Applicative (Rec1 f)
deriving instance Alternative f => Alternative (Rec1 f)
instance Monad f => Monad (Rec1 f) where Rec1 f a x >>= :: forall a b. Rec1 f a -> (a -> Rec1 f b) -> Rec1 f b >>= a -> Rec1 f b f = f b -> Rec1 f b forall k (f :: k -> *) (p :: k). f p -> Rec1 f p Rec1 (f a x f a -> (a -> f b) -> f b forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b >>= \a a -> Rec1 f b -> f b forall k (f :: k -> *) (p :: k). Rec1 f p -> f p unRec1 (a -> Rec1 f b f a a))
deriving instance MonadPlus f => MonadPlus (Rec1 f)
deriving instance Semigroup (f p) => Semigroup (Rec1 f p)
deriving instance Monoid (f p) => Monoid (Rec1 f p)
newtype K1 (i :: Type) c (p :: k) = K1 { forall k i c (p :: k). K1 i c p -> c
unK1 :: c }
deriving ( K1 i c p -> K1 i c p -> Bool
(K1 i c p -> K1 i c p -> Bool)
-> (K1 i c p -> K1 i c p -> Bool) -> Eq (K1 i c p)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall i c k (p :: k). Eq c => K1 i c p -> K1 i c p -> Bool
/= :: K1 i c p -> K1 i c p -> Bool
$c/= :: forall i c k (p :: k). Eq c => K1 i c p -> K1 i c p -> Bool
== :: K1 i c p -> K1 i c p -> Bool
$c== :: forall i c k (p :: k). Eq c => K1 i c p -> K1 i c p -> Bool
Eq
, Eq (K1 i c p)
Eq (K1 i c p)
-> (K1 i c p -> K1 i c p -> Ordering)
-> (K1 i c p -> K1 i c p -> Bool)
-> (K1 i c p -> K1 i c p -> Bool)
-> (K1 i c p -> K1 i c p -> Bool)
-> (K1 i c p -> K1 i c p -> Bool)
-> (K1 i c p -> K1 i c p -> K1 i c p)
-> (K1 i c p -> K1 i c p -> K1 i c p)
-> Ord (K1 i c p)
K1 i c p -> K1 i c p -> Bool
K1 i c p -> K1 i c p -> Ordering
K1 i c p -> K1 i c p -> K1 i c p
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 {i} {c} {k} {p :: k}. Ord c => Eq (K1 i c p)
forall i c k (p :: k). Ord c => K1 i c p -> K1 i c p -> Bool
forall i c k (p :: k). Ord c => K1 i c p -> K1 i c p -> Ordering
forall i c k (p :: k). Ord c => K1 i c p -> K1 i c p -> K1 i c p
min :: K1 i c p -> K1 i c p -> K1 i c p
$cmin :: forall i c k (p :: k). Ord c => K1 i c p -> K1 i c p -> K1 i c p
max :: K1 i c p -> K1 i c p -> K1 i c p
$cmax :: forall i c k (p :: k). Ord c => K1 i c p -> K1 i c p -> K1 i c p
= :: K1 i c p -> K1 i c p -> Bool $c>= :: forall i c k (p :: k). Ord c => K1 i c p -> K1 i c p -> Bool :: K1 i c p -> K1 i c p -> Bool $c> :: forall i c k (p :: k). Ord c => K1 i c p -> K1 i c p -> Bool <= :: K1 i c p -> K1 i c p -> Bool $c<= :: forall i c k (p :: k). Ord c => K1 i c p -> K1 i c p -> Bool < :: K1 i c p -> K1 i c p -> Bool $c< :: forall i c k (p :: k). Ord c => K1 i c p -> K1 i c p -> Bool compare :: K1 i c p -> K1 i c p -> Ordering $ccompare :: forall i c k (p :: k). Ord c => K1 i c p -> K1 i c p -> Ordering Ord
, ReadPrec [K1 i c p] ReadPrec (K1 i c p) Int -> ReadS (K1 i c p) ReadS [K1 i c p] (Int -> ReadS (K1 i c p)) -> ReadS [K1 i c p] -> ReadPrec (K1 i c p) -> ReadPrec [K1 i c p] -> Read (K1 i c p) forall a. (Int -> ReadS a) -> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a forall i c k (p :: k). Read c => ReadPrec [K1 i c p] forall i c k (p :: k). Read c => ReadPrec (K1 i c p) forall i c k (p :: k). Read c => Int -> ReadS (K1 i c p) forall i c k (p :: k). Read c => ReadS [K1 i c p] readListPrec :: ReadPrec [K1 i c p] $creadListPrec :: forall i c k (p :: k). Read c => ReadPrec [K1 i c p] readPrec :: ReadPrec (K1 i c p) $creadPrec :: forall i c k (p :: k). Read c => ReadPrec (K1 i c p) readList :: ReadS [K1 i c p] $creadList :: forall i c k (p :: k). Read c => ReadS [K1 i c p] readsPrec :: Int -> ReadS (K1 i c p) $creadsPrec :: forall i c k (p :: k). Read c => Int -> ReadS (K1 i c p) Read
, Int -> K1 i c p -> ShowS [K1 i c p] -> ShowS K1 i c p -> String (Int -> K1 i c p -> ShowS) -> (K1 i c p -> String) -> ([K1 i c p] -> ShowS) -> Show (K1 i c p) forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a forall i c k (p :: k). Show c => Int -> K1 i c p -> ShowS forall i c k (p :: k). Show c => [K1 i c p] -> ShowS forall i c k (p :: k). Show c => K1 i c p -> String showList :: [K1 i c p] -> ShowS $cshowList :: forall i c k (p :: k). Show c => [K1 i c p] -> ShowS show :: K1 i c p -> String $cshow :: forall i c k (p :: k). Show c => K1 i c p -> String showsPrec :: Int -> K1 i c p -> ShowS $cshowsPrec :: forall i c k (p :: k). Show c => Int -> K1 i c p -> ShowS Show
, (forall a b. (a -> b) -> K1 i c a -> K1 i c b) -> (forall a b. a -> K1 i c b -> K1 i c a) -> Functor (K1 i c) forall a b. a -> K1 i c b -> K1 i c a forall a b. (a -> b) -> K1 i c a -> K1 i c b forall i c a b. a -> K1 i c b -> K1 i c a forall i c a b. (a -> b) -> K1 i c a -> K1 i c b forall (f :: * -> *). (forall a b. (a -> b) -> f a -> f b) -> (forall a b. a -> f b -> f a) -> Functor f <$ :: forall a b. a -> K1 i c b -> K1 i c a c<c<c< :: forall i c a b. a -> K1 i c b -> K1 i c a fmap :: forall a b. (a -> b) -> K1 i c a -> K1 i c b $cfmap :: forall i c a b. (a -> b) -> K1 i c a -> K1 i c b Functor
, (forall x. K1 i c p -> Rep (K1 i c p) x) -> (forall x. Rep (K1 i c p) x -> K1 i c p) -> Generic (K1 i c p) forall x. K1 i c p -> Rep (K1 i c p) x forall x. Rep (K1 i c p) x -> K1 i c p forall a. (forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a forall i c k (p :: k) x. K1 i c p -> Rep (K1 i c p) x forall i c k (p :: k) x. Rep (K1 i c p) x -> K1 i c p $cto :: forall i c k (p :: k) x. Rep (K1 i c p) x -> K1 i c p $cfrom :: forall i c k (p :: k) x. K1 i c p -> Rep (K1 i c p) x Generic
, (forall (a :: k). K1 i c a -> Rep1 (K1 i c) a) -> (forall (a :: k). Rep1 (K1 i c) a -> K1 i c a) -> Generic1 (K1 i c) forall (a :: k). K1 i c a -> Rep1 (K1 i c) a forall (a :: k). Rep1 (K1 i c) a -> K1 i c a forall k i c (a :: k). K1 i c a -> Rep1 (K1 i c) a forall k i c (a :: k). Rep1 (K1 i c) a -> K1 i c a forall k (f :: k -> *). (forall (a :: k). f a -> Rep1 f a) -> (forall (a :: k). Rep1 f a -> f a) -> Generic1 f $cto1 :: forall k i c (a :: k). Rep1 (K1 i c) a -> K1 i c a $cfrom1 :: forall k i c (a :: k). K1 i c a -> Rep1 (K1 i c) a Generic1 )
instance Monoid c => Applicative (K1 i c) where pure :: forall a. a -> K1 i c a pure a _ = c -> K1 i c a forall k i c (p :: k). c -> K1 i c p K1 c forall a. Monoid a => a mempty liftA2 :: forall a b c. (a -> b -> c) -> K1 i c a -> K1 i c b -> K1 i c c liftA2 = \a -> b -> c _ -> (c -> c -> c) -> K1 i c a -> K1 i c b -> K1 i c c coerce (c -> c -> c forall a. Monoid a => a -> a -> a mappend :: c -> c -> c) <*> :: forall a b. K1 i c (a -> b) -> K1 i c a -> K1 i c b (<*>) = (c -> c -> c) -> K1 i c (a -> b) -> K1 i c a -> K1 i c b coerce (c -> c -> c forall a. Monoid a => a -> a -> a mappend :: c -> c -> c)
deriving instance Semigroup c => Semigroup (K1 i c p)
deriving instance Monoid c => Monoid (K1 i c p)
deriving instance Applicative f => Applicative (M1 i c f)
deriving instance Alternative f => Alternative (M1 i c f)
deriving instance Monad f => Monad (M1 i c f)
deriving instance MonadPlus f => MonadPlus (M1 i c f)
deriving instance Semigroup (f p) => Semigroup (M1 i c f p)
deriving instance Monoid (f p) => Monoid (M1 i c f p)
newtype M1 (i :: Type) (c :: Meta) (f :: k -> Type) (p :: k) =
M1 { forall k i (c :: Meta) (f :: k -> *) (p :: k). M1 i c f p -> f p
unM1 :: f p }
deriving ( M1 i c f p -> M1 i c f p -> Bool
(M1 i c f p -> M1 i c f p -> Bool)
-> (M1 i c f p -> M1 i c f p -> Bool) -> Eq (M1 i c f p)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall i (c :: Meta) k (f :: k -> *) (p :: k).
Eq (f p) =>
M1 i c f p -> M1 i c f p -> Bool
/= :: M1 i c f p -> M1 i c f p -> Bool
$c/= :: forall i (c :: Meta) k (f :: k -> *) (p :: k).
Eq (f p) =>
M1 i c f p -> M1 i c f p -> Bool
== :: M1 i c f p -> M1 i c f p -> Bool
$c== :: forall i (c :: Meta) k (f :: k -> *) (p :: k).
Eq (f p) =>
M1 i c f p -> M1 i c f p -> Bool
Eq
, Eq (M1 i c f p)
Eq (M1 i c f p)
-> (M1 i c f p -> M1 i c f p -> Ordering)
-> (M1 i c f p -> M1 i c f p -> Bool)
-> (M1 i c f p -> M1 i c f p -> Bool)
-> (M1 i c f p -> M1 i c f p -> Bool)
-> (M1 i c f p -> M1 i c f p -> Bool)
-> (M1 i c f p -> M1 i c f p -> M1 i c f p)
-> (M1 i c f p -> M1 i c f p -> M1 i c f p)
-> Ord (M1 i c f p)
M1 i c f p -> M1 i c f p -> Bool
M1 i c f p -> M1 i c f p -> Ordering
M1 i c f p -> M1 i c f p -> M1 i c f p
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 {i} {c :: Meta} {k} {f :: k -> *} {p :: k}.
Ord (f p) =>
Eq (M1 i c f p)
forall i (c :: Meta) k (f :: k -> *) (p :: k).
Ord (f p) =>
M1 i c f p -> M1 i c f p -> Bool
forall i (c :: Meta) k (f :: k -> *) (p :: k).
Ord (f p) =>
M1 i c f p -> M1 i c f p -> Ordering
forall i (c :: Meta) k (f :: k -> *) (p :: k).
Ord (f p) =>
M1 i c f p -> M1 i c f p -> M1 i c f p
min :: M1 i c f p -> M1 i c f p -> M1 i c f p
$cmin :: forall i (c :: Meta) k (f :: k -> *) (p :: k).
Ord (f p) =>
M1 i c f p -> M1 i c f p -> M1 i c f p
max :: M1 i c f p -> M1 i c f p -> M1 i c f p
$cmax :: forall i (c :: Meta) k (f :: k -> *) (p :: k).
Ord (f p) =>
M1 i c f p -> M1 i c f p -> M1 i c f p
= :: M1 i c f p -> M1 i c f p -> Bool $c>= :: forall i (c :: Meta) k (f :: k -> *) (p :: k). Ord (f p) => M1 i c f p -> M1 i c f p -> Bool :: M1 i c f p -> M1 i c f p -> Bool $c> :: forall i (c :: Meta) k (f :: k -> *) (p :: k). Ord (f p) => M1 i c f p -> M1 i c f p -> Bool <= :: M1 i c f p -> M1 i c f p -> Bool $c<= :: forall i (c :: Meta) k (f :: k -> *) (p :: k). Ord (f p) => M1 i c f p -> M1 i c f p -> Bool < :: M1 i c f p -> M1 i c f p -> Bool $c< :: forall i (c :: Meta) k (f :: k -> *) (p :: k). Ord (f p) => M1 i c f p -> M1 i c f p -> Bool compare :: M1 i c f p -> M1 i c f p -> Ordering $ccompare :: forall i (c :: Meta) k (f :: k -> *) (p :: k). Ord (f p) => M1 i c f p -> M1 i c f p -> Ordering Ord
, ReadPrec [M1 i c f p] ReadPrec (M1 i c f p) Int -> ReadS (M1 i c f p) ReadS [M1 i c f p] (Int -> ReadS (M1 i c f p)) -> ReadS [M1 i c f p] -> ReadPrec (M1 i c f p) -> ReadPrec [M1 i c f p] -> Read (M1 i c f p) forall a. (Int -> ReadS a) -> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a forall i (c :: Meta) k (f :: k -> *) (p :: k). Read (f p) => ReadPrec [M1 i c f p] forall i (c :: Meta) k (f :: k -> *) (p :: k). Read (f p) => ReadPrec (M1 i c f p) forall i (c :: Meta) k (f :: k -> *) (p :: k). Read (f p) => Int -> ReadS (M1 i c f p) forall i (c :: Meta) k (f :: k -> *) (p :: k). Read (f p) => ReadS [M1 i c f p] readListPrec :: ReadPrec [M1 i c f p] $creadListPrec :: forall i (c :: Meta) k (f :: k -> *) (p :: k). Read (f p) => ReadPrec [M1 i c f p] readPrec :: ReadPrec (M1 i c f p) $creadPrec :: forall i (c :: Meta) k (f :: k -> *) (p :: k). Read (f p) => ReadPrec (M1 i c f p) readList :: ReadS [M1 i c f p] $creadList :: forall i (c :: Meta) k (f :: k -> *) (p :: k). Read (f p) => ReadS [M1 i c f p] readsPrec :: Int -> ReadS (M1 i c f p) $creadsPrec :: forall i (c :: Meta) k (f :: k -> *) (p :: k). Read (f p) => Int -> ReadS (M1 i c f p) Read
, Int -> M1 i c f p -> ShowS [M1 i c f p] -> ShowS M1 i c f p -> String (Int -> M1 i c f p -> ShowS) -> (M1 i c f p -> String) -> ([M1 i c f p] -> ShowS) -> Show (M1 i c f p) forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a forall i (c :: Meta) k (f :: k -> *) (p :: k). Show (f p) => Int -> M1 i c f p -> ShowS forall i (c :: Meta) k (f :: k -> *) (p :: k). Show (f p) => [M1 i c f p] -> ShowS forall i (c :: Meta) k (f :: k -> *) (p :: k). Show (f p) => M1 i c f p -> String showList :: [M1 i c f p] -> ShowS $cshowList :: forall i (c :: Meta) k (f :: k -> *) (p :: k). Show (f p) => [M1 i c f p] -> ShowS show :: M1 i c f p -> String $cshow :: forall i (c :: Meta) k (f :: k -> *) (p :: k). Show (f p) => M1 i c f p -> String showsPrec :: Int -> M1 i c f p -> ShowS $cshowsPrec :: forall i (c :: Meta) k (f :: k -> *) (p :: k). Show (f p) => Int -> M1 i c f p -> ShowS Show
, (forall a b. (a -> b) -> M1 i c f a -> M1 i c f b) -> (forall a b. a -> M1 i c f b -> M1 i c f a) -> Functor (M1 i c f) forall a b. a -> M1 i c f b -> M1 i c f a forall a b. (a -> b) -> M1 i c f a -> M1 i c f b forall i (c :: Meta) (f :: * -> *) a b. Functor f => a -> M1 i c f b -> M1 i c f a forall i (c :: Meta) (f :: * -> *) a b. Functor f => (a -> b) -> M1 i c f a -> M1 i c f b forall (f :: * -> *). (forall a b. (a -> b) -> f a -> f b) -> (forall a b. a -> f b -> f a) -> Functor f <$ :: forall a b. a -> M1 i c f b -> M1 i c f a c<c<c< :: forall i (c :: Meta) (f :: * -> *) a b. Functor f => a -> M1 i c f b -> M1 i c f a fmap :: forall a b. (a -> b) -> M1 i c f a -> M1 i c f b $cfmap :: forall i (c :: Meta) (f :: * -> *) a b. Functor f => (a -> b) -> M1 i c f a -> M1 i c f b Functor
, (forall x. M1 i c f p -> Rep (M1 i c f p) x) -> (forall x. Rep (M1 i c f p) x -> M1 i c f p) -> Generic (M1 i c f p) forall x. M1 i c f p -> Rep (M1 i c f p) x forall x. Rep (M1 i c f p) x -> M1 i c f p forall a. (forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a forall i (c :: Meta) k (f :: k -> *) (p :: k) x. M1 i c f p -> Rep (M1 i c f p) x forall i (c :: Meta) k (f :: k -> *) (p :: k) x. Rep (M1 i c f p) x -> M1 i c f p $cto :: forall i (c :: Meta) k (f :: k -> *) (p :: k) x. Rep (M1 i c f p) x -> M1 i c f p $cfrom :: forall i (c :: Meta) k (f :: k -> *) (p :: k) x. M1 i c f p -> Rep (M1 i c f p) x Generic
, (forall (a :: k). M1 i c f a -> Rep1 (M1 i c f) a) -> (forall (a :: k). Rep1 (M1 i c f) a -> M1 i c f a) -> Generic1 (M1 i c f) forall (a :: k). M1 i c f a -> Rep1 (M1 i c f) a forall (a :: k). Rep1 (M1 i c f) a -> M1 i c f a forall i (c :: Meta) k (f :: k -> *) (a :: k). M1 i c f a -> Rep1 (M1 i c f) a forall i (c :: Meta) k (f :: k -> *) (a :: k). Rep1 (M1 i c f) a -> M1 i c f a forall k (f :: k -> *). (forall (a :: k). f a -> Rep1 f a) -> (forall (a :: k). Rep1 f a -> f a) -> Generic1 f $cto1 :: forall i (c :: Meta) k (f :: k -> *) (a :: k). Rep1 (M1 i c f) a -> M1 i c f a $cfrom1 :: forall i (c :: Meta) k (f :: k -> *) (a :: k). M1 i c f a -> Rep1 (M1 i c f) a Generic1 )
infixr 5 :+:
data (:+:) (f :: k -> Type) (g :: k -> Type) (p :: k) = L1 (f p) | R1 (g p)
deriving ( (:+:) f g p -> (:+:) f g p -> Bool
((:+:) f g p -> (:+:) f g p -> Bool)
-> ((:+:) f g p -> (:+:) f g p -> Bool) -> Eq ((:+:) f g p)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall k (f :: k -> *) (g :: k -> *) (p :: k).
(Eq (f p), Eq (g p)) =>
(:+:) f g p -> (:+:) f g p -> Bool
/= :: (:+:) f g p -> (:+:) f g p -> Bool
$c/= :: forall k (f :: k -> *) (g :: k -> *) (p :: k).
(Eq (f p), Eq (g p)) =>
(:+:) f g p -> (:+:) f g p -> Bool
== :: (:+:) f g p -> (:+:) f g p -> Bool
$c== :: forall k (f :: k -> *) (g :: k -> *) (p :: k).
(Eq (f p), Eq (g p)) =>
(:+:) f g p -> (:+:) f g p -> Bool
Eq
, Eq ((:+:) f g p)
Eq ((:+:) f g p)
-> ((:+:) f g p -> (:+:) f g p -> Ordering)
-> ((:+:) f g p -> (:+:) f g p -> Bool)
-> ((:+:) f g p -> (:+:) f g p -> Bool)
-> ((:+:) f g p -> (:+:) f g p -> Bool)
-> ((:+:) f g p -> (:+:) f g p -> Bool)
-> ((:+:) f g p -> (:+:) f g p -> (:+:) f g p)
-> ((:+:) f g p -> (:+:) f g p -> (:+:) f g p)
-> Ord ((:+:) f g p)
(:+:) f g p -> (:+:) f g p -> Bool
(:+:) f g p -> (:+:) f g p -> Ordering
(:+:) f g p -> (:+:) f g p -> (:+:) f g p
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 {k} {f :: k -> *} {g :: k -> *} {p :: k}.
(Ord (f p), Ord (g p)) =>
Eq ((:+:) f g p)
forall k (f :: k -> *) (g :: k -> *) (p :: k).
(Ord (f p), Ord (g p)) =>
(:+:) f g p -> (:+:) f g p -> Bool
forall k (f :: k -> *) (g :: k -> *) (p :: k).
(Ord (f p), Ord (g p)) =>
(:+:) f g p -> (:+:) f g p -> Ordering
forall k (f :: k -> *) (g :: k -> *) (p :: k).
(Ord (f p), Ord (g p)) =>
(:+:) f g p -> (:+:) f g p -> (:+:) f g p
min :: (:+:) f g p -> (:+:) f g p -> (:+:) f g p
$cmin :: forall k (f :: k -> *) (g :: k -> *) (p :: k).
(Ord (f p), Ord (g p)) =>
(:+:) f g p -> (:+:) f g p -> (:+:) f g p
max :: (:+:) f g p -> (:+:) f g p -> (:+:) f g p
$cmax :: forall k (f :: k -> *) (g :: k -> *) (p :: k).
(Ord (f p), Ord (g p)) =>
(:+:) f g p -> (:+:) f g p -> (:+:) f g p
= :: (:+:) f g p -> (:+:) f g p -> Bool $c>= :: forall k (f :: k -> *) (g :: k -> *) (p :: k). (Ord (f p), Ord (g p)) => (:+:) f g p -> (:+:) f g p -> Bool :: (:+:) f g p -> (:+:) f g p -> Bool $c> :: forall k (f :: k -> *) (g :: k -> *) (p :: k). (Ord (f p), Ord (g p)) => (:+:) f g p -> (:+:) f g p -> Bool <= :: (:+:) f g p -> (:+:) f g p -> Bool $c<= :: forall k (f :: k -> *) (g :: k -> *) (p :: k). (Ord (f p), Ord (g p)) => (:+:) f g p -> (:+:) f g p -> Bool < :: (:+:) f g p -> (:+:) f g p -> Bool $c< :: forall k (f :: k -> *) (g :: k -> *) (p :: k). (Ord (f p), Ord (g p)) => (:+:) f g p -> (:+:) f g p -> Bool compare :: (:+:) f g p -> (:+:) f g p -> Ordering $ccompare :: forall k (f :: k -> *) (g :: k -> *) (p :: k). (Ord (f p), Ord (g p)) => (:+:) f g p -> (:+:) f g p -> Ordering Ord
, ReadPrec [(:+:) f g p] ReadPrec ((:+:) f g p) Int -> ReadS ((:+:) f g p) ReadS [(:+:) f g p] (Int -> ReadS ((:+:) f g p)) -> ReadS [(:+:) f g p] -> ReadPrec ((:+:) f g p) -> ReadPrec [(:+:) f g p] -> Read ((:+:) f g p) forall a. (Int -> ReadS a) -> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a forall k (f :: k -> *) (g :: k -> *) (p :: k). (Read (f p), Read (g p)) => ReadPrec [(:+:) f g p] forall k (f :: k -> *) (g :: k -> *) (p :: k). (Read (f p), Read (g p)) => ReadPrec ((:+:) f g p) forall k (f :: k -> *) (g :: k -> *) (p :: k). (Read (f p), Read (g p)) => Int -> ReadS ((:+:) f g p) forall k (f :: k -> *) (g :: k -> *) (p :: k). (Read (f p), Read (g p)) => ReadS [(:+:) f g p] readListPrec :: ReadPrec [(:+:) f g p] $creadListPrec :: forall k (f :: k -> *) (g :: k -> *) (p :: k). (Read (f p), Read (g p)) => ReadPrec [(:+:) f g p] readPrec :: ReadPrec ((:+:) f g p) $creadPrec :: forall k (f :: k -> *) (g :: k -> *) (p :: k). (Read (f p), Read (g p)) => ReadPrec ((:+:) f g p) readList :: ReadS [(:+:) f g p] $creadList :: forall k (f :: k -> *) (g :: k -> *) (p :: k). (Read (f p), Read (g p)) => ReadS [(:+:) f g p] readsPrec :: Int -> ReadS ((:+:) f g p) $creadsPrec :: forall k (f :: k -> *) (g :: k -> *) (p :: k). (Read (f p), Read (g p)) => Int -> ReadS ((:+:) f g p) Read
, Int -> (:+:) f g p -> ShowS [(:+:) f g p] -> ShowS (:+:) f g p -> String (Int -> (:+:) f g p -> ShowS) -> ((:+:) f g p -> String) -> ([(:+:) f g p] -> ShowS) -> Show ((:+:) f g p) forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a forall k (f :: k -> *) (g :: k -> *) (p :: k). (Show (f p), Show (g p)) => Int -> (:+:) f g p -> ShowS forall k (f :: k -> *) (g :: k -> *) (p :: k). (Show (f p), Show (g p)) => [(:+:) f g p] -> ShowS forall k (f :: k -> *) (g :: k -> *) (p :: k). (Show (f p), Show (g p)) => (:+:) f g p -> String showList :: [(:+:) f g p] -> ShowS $cshowList :: forall k (f :: k -> *) (g :: k -> *) (p :: k). (Show (f p), Show (g p)) => [(:+:) f g p] -> ShowS show :: (:+:) f g p -> String $cshow :: forall k (f :: k -> *) (g :: k -> *) (p :: k). (Show (f p), Show (g p)) => (:+:) f g p -> String showsPrec :: Int -> (:+:) f g p -> ShowS $cshowsPrec :: forall k (f :: k -> *) (g :: k -> *) (p :: k). (Show (f p), Show (g p)) => Int -> (:+:) f g p -> ShowS Show
, (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<c<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 x. (:+:) f g p -> Rep ((:+:) f g p) x) -> (forall x. Rep ((:+:) f g p) x -> (:+:) f g p) -> Generic ((:+:) f g p) forall x. (:+:) f g p -> Rep ((:+:) f g p) x forall x. Rep ((:+:) f g p) x -> (:+:) f g p forall a. (forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a forall k (f :: k -> *) (g :: k -> *) (p :: k) x. (:+:) f g p -> Rep ((:+:) f g p) x forall k (f :: k -> *) (g :: k -> *) (p :: k) x. Rep ((:+:) f g p) x -> (:+:) f g p $cto :: forall k (f :: k -> *) (g :: k -> *) (p :: k) x. Rep ((:+:) f g p) x -> (:+:) f g p $cfrom :: forall k (f :: k -> *) (g :: k -> *) (p :: k) x. (:+:) f g p -> Rep ((:+:) f g p) x 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). (:+:) f g a -> Rep1 (f :+: g) a forall (a :: k). Rep1 (f :+: g) a -> (:+:) 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 k (f :: k -> *) (g :: k -> *) (a :: k). (:+:) f g a -> Rep1 (f :+: g) a forall k (f :: k -> *) (g :: k -> *) (a :: k). Rep1 (f :+: g) a -> (:+:) f g a $cto1 :: forall k (f :: k -> *) (g :: k -> *) (a :: k). Rep1 (f :+: g) a -> (:+:) f g a $cfrom1 :: forall k (f :: k -> *) (g :: k -> *) (a :: k). (:+:) f g a -> Rep1 (f :+: g) a Generic1 )
infixr 6 :*:
data (:*:) (f :: k -> Type) (g :: k -> Type) (p :: k) = f p :*: g p
deriving ( (::) f g p -> (::) f g p -> Bool
((::) f g p -> (::) f g p -> Bool)
-> ((::) f g p -> (::) f g p -> Bool) -> Eq ((::) f g p)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall k (f :: k -> ) (g :: k -> ) (p :: k).
(Eq (f p), Eq (g p)) =>
(::) f g p -> (::) f g p -> Bool
/= :: (::) f g p -> (::) f g p -> Bool
$c/= :: forall k (f :: k -> ) (g :: k -> ) (p :: k).
(Eq (f p), Eq (g p)) =>
(::) f g p -> (::) f g p -> Bool
== :: (::) f g p -> (::) f g p -> Bool
$c== :: forall k (f :: k -> ) (g :: k -> ) (p :: k).
(Eq (f p), Eq (g p)) =>
(::) f g p -> (::) f g p -> Bool
Eq
, Eq ((::) f g p)
Eq ((::) f g p)
-> ((::) f g p -> (::) f g p -> Ordering)
-> ((::) f g p -> (::) f g p -> Bool)
-> ((::) f g p -> (::) f g p -> Bool)
-> ((::) f g p -> (::) f g p -> Bool)
-> ((::) f g p -> (::) f g p -> Bool)
-> ((::) f g p -> (::) f g p -> (::) f g p)
-> ((::) f g p -> (::) f g p -> (::) f g p)
-> Ord ((::) f g p)
(::) f g p -> (::) f g p -> Bool
(::) f g p -> (::) f g p -> Ordering
(::) f g p -> (::) f g p -> (::) f g p
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 {k} {f :: k -> } {g :: k -> } {p :: k}.
(Ord (f p), Ord (g p)) =>
Eq ((::) f g p)
forall k (f :: k -> ) (g :: k -> ) (p :: k).
(Ord (f p), Ord (g p)) =>
(::) f g p -> (::) f g p -> Bool
forall k (f :: k -> ) (g :: k -> ) (p :: k).
(Ord (f p), Ord (g p)) =>
(::) f g p -> (::) f g p -> Ordering
forall k (f :: k -> ) (g :: k -> ) (p :: k).
(Ord (f p), Ord (g p)) =>
(::) f g p -> (::) f g p -> (::) f g p
min :: (::) f g p -> (::) f g p -> (::) f g p
$cmin :: forall k (f :: k -> ) (g :: k -> ) (p :: k).
(Ord (f p), Ord (g p)) =>
(::) f g p -> (::) f g p -> (::) f g p
max :: (::) f g p -> (::) f g p -> (::) f g p
$cmax :: forall k (f :: k -> ) (g :: k -> ) (p :: k).
(Ord (f p), Ord (g p)) =>
(::) f g p -> (::) f g p -> (:*:) f g p
= :: (::) f g p -> (::) f g p -> Bool $c>= :: forall k (f :: k -> ) (g :: k -> ) (p :: k). (Ord (f p), Ord (g p)) => (::) f g p -> (::) f g p -> Bool :: (::) f g p -> (::) f g p -> Bool $c> :: forall k (f :: k -> ) (g :: k -> ) (p :: k). (Ord (f p), Ord (g p)) => (::) f g p -> (::) f g p -> Bool <= :: (::) f g p -> (::) f g p -> Bool $c<= :: forall k (f :: k -> ) (g :: k -> ) (p :: k). (Ord (f p), Ord (g p)) => (::) f g p -> (::) f g p -> Bool < :: (::) f g p -> (::) f g p -> Bool $c< :: forall k (f :: k -> ) (g :: k -> ) (p :: k). (Ord (f p), Ord (g p)) => (::) f g p -> (::) f g p -> Bool compare :: (::) f g p -> (::) f g p -> Ordering $ccompare :: forall k (f :: k -> ) (g :: k -> ) (p :: k). (Ord (f p), Ord (g p)) => (::) f g p -> (::) f g p -> Ordering Ord
, ReadPrec [(::) f g p] ReadPrec ((::) f g p) Int -> ReadS ((::) f g p) ReadS [(::) f g p] (Int -> ReadS ((::) f g p)) -> ReadS [(::) f g p] -> ReadPrec ((::) f g p) -> ReadPrec [(::) f g p] -> Read ((::) f g p) forall a. (Int -> ReadS a) -> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a forall k (f :: k -> ) (g :: k -> ) (p :: k). (Read (f p), Read (g p)) => ReadPrec [(::) f g p] forall k (f :: k -> ) (g :: k -> ) (p :: k). (Read (f p), Read (g p)) => ReadPrec ((::) f g p) forall k (f :: k -> ) (g :: k -> ) (p :: k). (Read (f p), Read (g p)) => Int -> ReadS ((::) f g p) forall k (f :: k -> ) (g :: k -> ) (p :: k). (Read (f p), Read (g p)) => ReadS [(::) f g p] readListPrec :: ReadPrec [(::) f g p] $creadListPrec :: forall k (f :: k -> ) (g :: k -> ) (p :: k). (Read (f p), Read (g p)) => ReadPrec [(::) f g p] readPrec :: ReadPrec ((::) f g p) $creadPrec :: forall k (f :: k -> ) (g :: k -> ) (p :: k). (Read (f p), Read (g p)) => ReadPrec ((::) f g p) readList :: ReadS [(::) f g p] $creadList :: forall k (f :: k -> ) (g :: k -> ) (p :: k). (Read (f p), Read (g p)) => ReadS [(::) f g p] readsPrec :: Int -> ReadS ((::) f g p) $creadsPrec :: forall k (f :: k -> ) (g :: k -> ) (p :: k). (Read (f p), Read (g p)) => Int -> ReadS ((::) f g p) Read
, Int -> (::) f g p -> ShowS [(::) f g p] -> ShowS (::) f g p -> String (Int -> (::) f g p -> ShowS) -> ((::) f g p -> String) -> ([(::) f g p] -> ShowS) -> Show ((::) f g p) forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a forall k (f :: k -> ) (g :: k -> ) (p :: k). (Show (f p), Show (g p)) => Int -> (::) f g p -> ShowS forall k (f :: k -> ) (g :: k -> ) (p :: k). (Show (f p), Show (g p)) => [(::) f g p] -> ShowS forall k (f :: k -> ) (g :: k -> ) (p :: k). (Show (f p), Show (g p)) => (::) f g p -> String showList :: [(::) f g p] -> ShowS $cshowList :: forall k (f :: k -> ) (g :: k -> ) (p :: k). (Show (f p), Show (g p)) => [(::) f g p] -> ShowS show :: (::) f g p -> String $cshow :: forall k (f :: k -> ) (g :: k -> ) (p :: k). (Show (f p), Show (g p)) => (::) f g p -> String showsPrec :: Int -> (::) f g p -> ShowS $cshowsPrec :: forall k (f :: k -> ) (g :: k -> ) (p :: k). (Show (f p), Show (g p)) => Int -> (::) f g p -> ShowS Show
, (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<c<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 x. (::) f g p -> Rep ((::) f g p) x) -> (forall x. Rep ((::) f g p) x -> (::) f g p) -> Generic ((::) f g p) forall x. (::) f g p -> Rep ((::) f g p) x forall x. Rep ((::) f g p) x -> (::) f g p forall a. (forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a forall k (f :: k -> ) (g :: k -> ) (p :: k) x. (::) f g p -> Rep ((::) f g p) x forall k (f :: k -> ) (g :: k -> ) (p :: k) x. Rep ((::) f g p) x -> (::) f g p $cto :: forall k (f :: k -> ) (g :: k -> ) (p :: k) x. Rep ((::) f g p) x -> (::) f g p $cfrom :: forall k (f :: k -> ) (g :: k -> ) (p :: k) x. (::) f g p -> Rep ((::) f g p) x 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). (::) f g a -> Rep1 (f :: g) a forall (a :: k). Rep1 (f :: g) a -> (:*:) 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 k (f :: k -> ) (g :: k -> ) (a :: k). (::) f g a -> Rep1 (f :: g) a forall k (f :: k -> ) (g :: k -> ) (a :: k). Rep1 (f :: g) a -> (::) f g a $cto1 :: forall k (f :: k -> ) (g :: k -> ) (a :: k). Rep1 (f :: g) a -> (::) f g a $cfrom1 :: forall k (f :: k -> ) (g :: k -> ) (a :: k). (::) f g a -> Rep1 (f :: g) a Generic1 )
instance (Applicative f, Applicative g) => Applicative (f :*: g) where pure :: forall a. a -> (::) f g a pure a a = a -> f a forall (f :: * -> ) a. Applicative f => a -> f a pure a a f a -> g a -> (::) f g a forall k (f :: k -> ) (g :: k -> ) (p :: k). f p -> g p -> (::) f g p :*: a -> g a forall (f :: * -> ) a. Applicative f => a -> f a pure a a (f (a -> b) f :*: g (a -> b) g) <*> :: forall a b. (::) f g (a -> b) -> (::) f g a -> (::) f g b <*> (f a x :*: g a y) = (f (a -> b) f f (a -> b) -> f a -> f b forall (f :: * -> ) a b. Applicative f => f (a -> b) -> f a -> f b <*> f a x) f b -> g b -> (::) f g b forall k (f :: k -> ) (g :: k -> ) (p :: k). f p -> g p -> (::) f g p :*: (g (a -> b) g g (a -> b) -> g a -> g b forall (f :: * -> ) a b. Applicative f => f (a -> b) -> f a -> f b <*> g a y) liftA2 :: forall a b c. (a -> b -> c) -> (::) f g a -> (::) f g b -> (:*:) f g c liftA2 a -> b -> c f (f a a :*: g a b) (f b x :*: g b y) = (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 a f b x f c -> g c -> (::) f g c forall k (f :: k -> *) (g :: k -> ) (p :: k). f p -> g p -> (::) f g p :*: (a -> b -> c) -> g a -> g b -> g c forall (f :: * -> *) a b c. Applicative f => (a -> b -> c) -> f a -> f b -> f c liftA2 a -> b -> c f g a b g b y
instance (Alternative f, Alternative g) => Alternative (f :*: g) where empty :: forall a. (::) f g a empty = f a forall (f :: * -> ) a. Alternative f => f a empty f a -> g a -> (::) f g a forall k (f :: k -> ) (g :: k -> ) (p :: k). f p -> g p -> (::) f g p :*: g a forall (f :: * -> ) a. Alternative f => f a empty (f a x1 :*: g a y1) <|> :: forall a. (::) f g a -> (::) f g a -> (::) f g a <|> (f a x2 :*: g a y2) = (f a x1 f a -> f a -> f a forall (f :: * -> ) a. Alternative f => f a -> f a -> f a <|> f a x2) f a -> g a -> (::) f g a forall k (f :: k -> *) (g :: k -> ) (p :: k). f p -> g p -> (::) f g p :*: (g a y1 g a -> g a -> g a forall (f :: * -> *) a. Alternative f => f a -> f a -> f a <|> g a y2)
instance (Monad f, Monad g) => Monad (f :*: g) where (f a m :*: g a n) >>= :: forall a b. (::) f g a -> (a -> (::) f g b) -> (::) f g b >>= a -> (::) f g b f = (f a m f a -> (a -> f b) -> f b forall (m :: * -> ) a b. Monad m => m a -> (a -> m b) -> m b >>= \a a -> (::) f g b -> f b forall {k} {f :: k -> } {g :: k -> } {p :: k}. (::) f g p -> f p fstP (a -> (::) f g b f a a)) f b -> g b -> (::) f g b forall k (f :: k -> ) (g :: k -> ) (p :: k). f p -> g p -> (::) f g p :*: (g a n g a -> (a -> g b) -> g b forall (m :: * -> ) a b. Monad m => m a -> (a -> m b) -> m b >>= \a a -> (::) f g b -> g b forall {k} {f :: k -> } {g :: k -> } {p :: k}. (::) f g p -> g p sndP (a -> (::) f g b f a a)) where fstP :: (::) f g p -> f p fstP (f p a :*: g p _) = f p a sndP :: (::) f g p -> g p sndP (f p _ :*: g p b) = g p b
instance (MonadPlus f, MonadPlus g) => MonadPlus (f :*: g)
instance (Semigroup (f p), Semigroup (g p)) => Semigroup ((f :*: g) p) where (f p x1 :*: g p y1) <> :: (::) f g p -> (::) f g p -> (::) f g p <> (f p x2 :*: g p y2) = (f p x1 f p -> f p -> f p forall a. Semigroup a => a -> a -> a <> f p x2) f p -> g p -> (::) f g p forall k (f :: k -> *) (g :: k -> ) (p :: k). f p -> g p -> (::) f g p :*: (g p y1 g p -> g p -> g p forall a. Semigroup a => a -> a -> a <> g p y2)
instance (Monoid (f p), Monoid (g p)) => Monoid ((f :*: g) p) where mempty :: (::) f g p mempty = f p forall a. Monoid a => a mempty f p -> g p -> (::) f g p forall k (f :: k -> *) (g :: k -> ) (p :: k). f p -> g p -> (::) f g p :*: g p forall a. Monoid a => a mempty
infixr 7 :.:
newtype (:.:) (f :: k2 -> Type) (g :: k1 -> k2) (p :: k1) =
Comp1 { forall k2 k1 (f :: k2 -> *) (g :: k1 -> k2) (p :: k1).
(:.:) f g p -> f (g p)
unComp1 :: f (g p) }
deriving ( (:.:) f g p -> (:.:) f g p -> Bool
((:.:) f g p -> (:.:) f g p -> Bool)
-> ((:.:) f g p -> (:.:) f g p -> Bool) -> Eq ((:.:) f g p)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall k2 (f :: k2 -> *) k1 (g :: k1 -> k2) (p :: k1).
Eq (f (g p)) =>
(:.:) f g p -> (:.:) f g p -> Bool
/= :: (:.:) f g p -> (:.:) f g p -> Bool
$c/= :: forall k2 (f :: k2 -> *) k1 (g :: k1 -> k2) (p :: k1).
Eq (f (g p)) =>
(:.:) f g p -> (:.:) f g p -> Bool
== :: (:.:) f g p -> (:.:) f g p -> Bool
$c== :: forall k2 (f :: k2 -> *) k1 (g :: k1 -> k2) (p :: k1).
Eq (f (g p)) =>
(:.:) f g p -> (:.:) f g p -> Bool
Eq
, Eq ((:.:) f g p)
Eq ((:.:) f g p)
-> ((:.:) f g p -> (:.:) f g p -> Ordering)
-> ((:.:) f g p -> (:.:) f g p -> Bool)
-> ((:.:) f g p -> (:.:) f g p -> Bool)
-> ((:.:) f g p -> (:.:) f g p -> Bool)
-> ((:.:) f g p -> (:.:) f g p -> Bool)
-> ((:.:) f g p -> (:.:) f g p -> (:.:) f g p)
-> ((:.:) f g p -> (:.:) f g p -> (:.:) f g p)
-> Ord ((:.:) f g p)
(:.:) f g p -> (:.:) f g p -> Bool
(:.:) f g p -> (:.:) f g p -> Ordering
(:.:) f g p -> (:.:) f g p -> (:.:) f g p
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} {p :: k1}.
Ord (f (g p)) =>
Eq ((:.:) f g p)
forall k2 (f :: k2 -> *) k1 (g :: k1 -> k2) (p :: k1).
Ord (f (g p)) =>
(:.:) f g p -> (:.:) f g p -> Bool
forall k2 (f :: k2 -> *) k1 (g :: k1 -> k2) (p :: k1).
Ord (f (g p)) =>
(:.:) f g p -> (:.:) f g p -> Ordering
forall k2 (f :: k2 -> *) k1 (g :: k1 -> k2) (p :: k1).
Ord (f (g p)) =>
(:.:) f g p -> (:.:) f g p -> (:.:) f g p
min :: (:.:) f g p -> (:.:) f g p -> (:.:) f g p
$cmin :: forall k2 (f :: k2 -> *) k1 (g :: k1 -> k2) (p :: k1).
Ord (f (g p)) =>
(:.:) f g p -> (:.:) f g p -> (:.:) f g p
max :: (:.:) f g p -> (:.:) f g p -> (:.:) f g p
$cmax :: forall k2 (f :: k2 -> *) k1 (g :: k1 -> k2) (p :: k1).
Ord (f (g p)) =>
(:.:) f g p -> (:.:) f g p -> (:.:) f g p
= :: (:.:) f g p -> (:.:) f g p -> Bool $c>= :: forall k2 (f :: k2 -> *) k1 (g :: k1 -> k2) (p :: k1). Ord (f (g p)) => (:.:) f g p -> (:.:) f g p -> Bool :: (:.:) f g p -> (:.:) f g p -> Bool $c> :: forall k2 (f :: k2 -> *) k1 (g :: k1 -> k2) (p :: k1). Ord (f (g p)) => (:.:) f g p -> (:.:) f g p -> Bool <= :: (:.:) f g p -> (:.:) f g p -> Bool $c<= :: forall k2 (f :: k2 -> *) k1 (g :: k1 -> k2) (p :: k1). Ord (f (g p)) => (:.:) f g p -> (:.:) f g p -> Bool < :: (:.:) f g p -> (:.:) f g p -> Bool $c< :: forall k2 (f :: k2 -> *) k1 (g :: k1 -> k2) (p :: k1). Ord (f (g p)) => (:.:) f g p -> (:.:) f g p -> Bool compare :: (:.:) f g p -> (:.:) f g p -> Ordering $ccompare :: forall k2 (f :: k2 -> *) k1 (g :: k1 -> k2) (p :: k1). Ord (f (g p)) => (:.:) f g p -> (:.:) f g p -> Ordering Ord
, ReadPrec [(:.:) f g p] ReadPrec ((:.:) f g p) Int -> ReadS ((:.:) f g p) ReadS [(:.:) f g p] (Int -> ReadS ((:.:) f g p)) -> ReadS [(:.:) f g p] -> ReadPrec ((:.:) f g p) -> ReadPrec [(:.:) f g p] -> Read ((:.:) f g p) forall a. (Int -> ReadS a) -> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a forall k2 (f :: k2 -> *) k1 (g :: k1 -> k2) (p :: k1). Read (f (g p)) => ReadPrec [(:.:) f g p] forall k2 (f :: k2 -> *) k1 (g :: k1 -> k2) (p :: k1). Read (f (g p)) => ReadPrec ((:.:) f g p) forall k2 (f :: k2 -> *) k1 (g :: k1 -> k2) (p :: k1). Read (f (g p)) => Int -> ReadS ((:.:) f g p) forall k2 (f :: k2 -> *) k1 (g :: k1 -> k2) (p :: k1). Read (f (g p)) => ReadS [(:.:) f g p] readListPrec :: ReadPrec [(:.:) f g p] $creadListPrec :: forall k2 (f :: k2 -> *) k1 (g :: k1 -> k2) (p :: k1). Read (f (g p)) => ReadPrec [(:.:) f g p] readPrec :: ReadPrec ((:.:) f g p) $creadPrec :: forall k2 (f :: k2 -> *) k1 (g :: k1 -> k2) (p :: k1). Read (f (g p)) => ReadPrec ((:.:) f g p) readList :: ReadS [(:.:) f g p] $creadList :: forall k2 (f :: k2 -> *) k1 (g :: k1 -> k2) (p :: k1). Read (f (g p)) => ReadS [(:.:) f g p] readsPrec :: Int -> ReadS ((:.:) f g p) $creadsPrec :: forall k2 (f :: k2 -> *) k1 (g :: k1 -> k2) (p :: k1). Read (f (g p)) => Int -> ReadS ((:.:) f g p) Read
, Int -> (:.:) f g p -> ShowS [(:.:) f g p] -> ShowS (:.:) f g p -> String (Int -> (:.:) f g p -> ShowS) -> ((:.:) f g p -> String) -> ([(:.:) f g p] -> ShowS) -> Show ((:.:) f g p) forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a forall k2 (f :: k2 -> *) k1 (g :: k1 -> k2) (p :: k1). Show (f (g p)) => Int -> (:.:) f g p -> ShowS forall k2 (f :: k2 -> *) k1 (g :: k1 -> k2) (p :: k1). Show (f (g p)) => [(:.:) f g p] -> ShowS forall k2 (f :: k2 -> *) k1 (g :: k1 -> k2) (p :: k1). Show (f (g p)) => (:.:) f g p -> String showList :: [(:.:) f g p] -> ShowS $cshowList :: forall k2 (f :: k2 -> *) k1 (g :: k1 -> k2) (p :: k1). Show (f (g p)) => [(:.:) f g p] -> ShowS show :: (:.:) f g p -> String $cshow :: forall k2 (f :: k2 -> *) k1 (g :: k1 -> k2) (p :: k1). Show (f (g p)) => (:.:) f g p -> String showsPrec :: Int -> (:.:) f g p -> ShowS $cshowsPrec :: forall k2 (f :: k2 -> *) k1 (g :: k1 -> k2) (p :: k1). Show (f (g p)) => Int -> (:.:) f g p -> ShowS Show
, (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<c<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 x. (:.:) f g p -> Rep ((:.:) f g p) x) -> (forall x. Rep ((:.:) f g p) x -> (:.:) f g p) -> Generic ((:.:) f g p) forall x. (:.:) f g p -> Rep ((:.:) f g p) x forall x. Rep ((:.:) f g p) x -> (:.:) f g p forall a. (forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a forall k2 (f :: k2 -> *) k1 (g :: k1 -> k2) (p :: k1) x. (:.:) f g p -> Rep ((:.:) f g p) x forall k2 (f :: k2 -> *) k1 (g :: k1 -> k2) (p :: k1) x. Rep ((:.:) f g p) x -> (:.:) f g p $cto :: forall k2 (f :: k2 -> *) k1 (g :: k1 -> k2) (p :: k1) x. Rep ((:.:) f g p) x -> (:.:) f g p $cfrom :: forall k2 (f :: k2 -> *) k1 (g :: k1 -> k2) (p :: k1) x. (:.:) f g p -> Rep ((:.:) f g p) x 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). (:.:) f g a -> Rep1 (f :.: g) a forall (a :: k). Rep1 (f :.: g) a -> (:.:) 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 => (:.:) f g a -> Rep1 (f :.: g) a forall (f :: * -> *) k (g :: k -> *) (a :: k). Functor f => Rep1 (f :.: g) a -> (:.:) 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 Generic1 )
instance (Applicative f, Applicative g) => Applicative (f :.: g) where pure :: forall a. a -> (:.:) f g a pure a x = f (g a) -> (:.:) f g a forall k2 k1 (f :: k2 -> *) (g :: k1 -> k2) (p :: k1). f (g p) -> (:.:) f g p Comp1 (g a -> f (g a) forall (f :: * -> *) a. Applicative f => a -> f a pure (a -> g a forall (f :: * -> *) a. Applicative f => a -> f a pure a x)) Comp1 f (g (a -> b)) f <*> :: forall a b. (:.:) f g (a -> b) -> (:.:) f g a -> (:.:) f g b <*> Comp1 f (g a) x = f (g b) -> (:.:) f g b forall k2 k1 (f :: k2 -> *) (g :: k1 -> k2) (p :: k1). f (g p) -> (:.:) f g p Comp1 ((g (a -> b) -> g a -> g b) -> f (g (a -> b)) -> f (g a) -> f (g b) forall (f :: * -> *) a b c. Applicative f => (a -> b -> c) -> f a -> f b -> f c liftA2 g (a -> b) -> g a -> g b forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b (<*>) f (g (a -> b)) f f (g a) x) liftA2 :: forall a b c. (a -> b -> c) -> (:.:) f g a -> (:.:) f g b -> (:.:) f g c liftA2 a -> b -> c f (Comp1 f (g a) x) (Comp1 f (g b) y) = f (g c) -> (:.:) f g c forall k2 k1 (f :: k2 -> *) (g :: k1 -> k2) (p :: k1). f (g p) -> (:.:) f g p Comp1 ((g a -> g b -> g c) -> f (g a) -> f (g b) -> f (g c) forall (f :: * -> *) a b c. Applicative f => (a -> b -> c) -> f a -> f b -> f c liftA2 ((a -> b -> c) -> g a -> g b -> g c forall (f :: * -> *) a b c. Applicative f => (a -> b -> c) -> f a -> f b -> f c liftA2 a -> b -> c f) f (g a) x f (g b) y)
instance (Alternative f, Applicative g) => Alternative (f :.: g) where empty :: forall a. (:.:) f g a empty = f (g a) -> (:.:) f g a forall k2 k1 (f :: k2 -> *) (g :: k1 -> k2) (p :: k1). f (g p) -> (:.:) f g p Comp1 f (g a) forall (f :: * -> *) a. Alternative f => f a empty <|> :: forall a. (:.:) f g a -> (:.:) f g a -> (:.:) f g a (<|>) = (f (g a) -> f (g a) -> f (g a)) -> (:.:) f g a -> (:.:) f g a -> (:.:) f g a coerce (f (g a) -> f (g a) -> f (g a) forall (f :: * -> *) a. Alternative f => f a -> f a -> f a (<|>) :: f (g a) -> f (g a) -> f (g a)) :: forall a . (f :.: g) a -> (f :.: g) a -> (f :.: g) a
deriving instance Semigroup (f (g p)) => Semigroup ((f :.: g) p)
deriving instance Monoid (f (g p)) => Monoid ((f :.: g) p)
data family URec (a :: Type) (p :: k)
data instance URec (Ptr ()) (p :: k) = UAddr { forall k (p :: k). URec (Ptr ()) p -> Addr#
uAddr# :: Addr# }
deriving ( URec (Ptr ()) p -> URec (Ptr ()) p -> Bool
(URec (Ptr ()) p -> URec (Ptr ()) p -> Bool)
-> (URec (Ptr ()) p -> URec (Ptr ()) p -> Bool)
-> Eq (URec (Ptr ()) p)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall k (p :: k). URec (Ptr ()) p -> URec (Ptr ()) p -> Bool
/= :: URec (Ptr ()) p -> URec (Ptr ()) p -> Bool
$c/= :: forall k (p :: k). URec (Ptr ()) p -> URec (Ptr ()) p -> Bool
== :: URec (Ptr ()) p -> URec (Ptr ()) p -> Bool
$c== :: forall k (p :: k). URec (Ptr ()) p -> URec (Ptr ()) p -> Bool
Eq
, Eq (URec (Ptr ()) p)
Eq (URec (Ptr ()) p)
-> (URec (Ptr ()) p -> URec (Ptr ()) p -> Ordering)
-> (URec (Ptr ()) p -> URec (Ptr ()) p -> Bool)
-> (URec (Ptr ()) p -> URec (Ptr ()) p -> Bool)
-> (URec (Ptr ()) p -> URec (Ptr ()) p -> Bool)
-> (URec (Ptr ()) p -> URec (Ptr ()) p -> Bool)
-> (URec (Ptr ()) p -> URec (Ptr ()) p -> URec (Ptr ()) p)
-> (URec (Ptr ()) p -> URec (Ptr ()) p -> URec (Ptr ()) p)
-> Ord (URec (Ptr ()) p)
URec (Ptr ()) p -> URec (Ptr ()) p -> Bool
URec (Ptr ()) p -> URec (Ptr ()) p -> Ordering
URec (Ptr ()) p -> URec (Ptr ()) p -> URec (Ptr ()) p
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 k (p :: k). Eq (URec (Ptr ()) p)
forall k (p :: k). URec (Ptr ()) p -> URec (Ptr ()) p -> Bool
forall k (p :: k). URec (Ptr ()) p -> URec (Ptr ()) p -> Ordering
forall k (p :: k).
URec (Ptr ()) p -> URec (Ptr ()) p -> URec (Ptr ()) p
min :: URec (Ptr ()) p -> URec (Ptr ()) p -> URec (Ptr ()) p
$cmin :: forall k (p :: k).
URec (Ptr ()) p -> URec (Ptr ()) p -> URec (Ptr ()) p
max :: URec (Ptr ()) p -> URec (Ptr ()) p -> URec (Ptr ()) p
$cmax :: forall k (p :: k).
URec (Ptr ()) p -> URec (Ptr ()) p -> URec (Ptr ()) p
= :: URec (Ptr ()) p -> URec (Ptr ()) p -> Bool $c>= :: forall k (p :: k). URec (Ptr ()) p -> URec (Ptr ()) p -> Bool :: URec (Ptr ()) p -> URec (Ptr ()) p -> Bool $c> :: forall k (p :: k). URec (Ptr ()) p -> URec (Ptr ()) p -> Bool <= :: URec (Ptr ()) p -> URec (Ptr ()) p -> Bool $c<= :: forall k (p :: k). URec (Ptr ()) p -> URec (Ptr ()) p -> Bool < :: URec (Ptr ()) p -> URec (Ptr ()) p -> Bool $c< :: forall k (p :: k). URec (Ptr ()) p -> URec (Ptr ()) p -> Bool compare :: URec (Ptr ()) p -> URec (Ptr ()) p -> Ordering $ccompare :: forall k (p :: k). URec (Ptr ()) p -> URec (Ptr ()) p -> Ordering Ord
, (forall a b. (a -> b) -> URec (Ptr ()) a -> URec (Ptr ()) b) -> (forall a b. a -> URec (Ptr ()) b -> URec (Ptr ()) a) -> Functor (URec (Ptr ())) forall a b. a -> URec (Ptr ()) b -> URec (Ptr ()) a forall a b. (a -> b) -> URec (Ptr ()) a -> URec (Ptr ()) b forall (f :: * -> *). (forall a b. (a -> b) -> f a -> f b) -> (forall a b. a -> f b -> f a) -> Functor f <$ :: forall a b. a -> URec (Ptr ()) b -> URec (Ptr ()) a c<c<c< :: forall a b. a -> URec (Ptr ()) b -> URec (Ptr ()) a fmap :: forall a b. (a -> b) -> URec (Ptr ()) a -> URec (Ptr ()) b $cfmap :: forall a b. (a -> b) -> URec (Ptr ()) a -> URec (Ptr ()) b Functor
, (forall x. URec (Ptr ()) p -> Rep (URec (Ptr ()) p) x) -> (forall x. Rep (URec (Ptr ()) p) x -> URec (Ptr ()) p) -> Generic (URec (Ptr ()) p) forall x. Rep (URec (Ptr ()) p) x -> URec (Ptr ()) p forall x. URec (Ptr ()) p -> Rep (URec (Ptr ()) p) x forall a. (forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a forall k (p :: k) x. Rep (URec (Ptr ()) p) x -> URec (Ptr ()) p forall k (p :: k) x. URec (Ptr ()) p -> Rep (URec (Ptr ()) p) x $cto :: forall k (p :: k) x. Rep (URec (Ptr ()) p) x -> URec (Ptr ()) p $cfrom :: forall k (p :: k) x. URec (Ptr ()) p -> Rep (URec (Ptr ()) p) x Generic
, (forall (a :: k). URec (Ptr ()) a -> Rep1 (URec (Ptr ())) a) -> (forall (a :: k). Rep1 (URec (Ptr ())) a -> URec (Ptr ()) a) -> Generic1 (URec (Ptr ())) forall (a :: k). Rep1 (URec (Ptr ())) a -> URec (Ptr ()) a forall (a :: k). URec (Ptr ()) a -> Rep1 (URec (Ptr ())) a forall k (a :: k). Rep1 (URec (Ptr ())) a -> URec (Ptr ()) a forall k (a :: k). URec (Ptr ()) a -> Rep1 (URec (Ptr ())) a forall k (f :: k -> *). (forall (a :: k). f a -> Rep1 f a) -> (forall (a :: k). Rep1 f a -> f a) -> Generic1 f $cto1 :: forall k (a :: k). Rep1 (URec (Ptr ())) a -> URec (Ptr ()) a $cfrom1 :: forall k (a :: k). URec (Ptr ()) a -> Rep1 (URec (Ptr ())) a Generic1 )
data instance URec Char (p :: k) = UChar { forall k (p :: k). URec Char p -> Char#
uChar# :: Char# }
deriving ( URec Char p -> URec Char p -> Bool
(URec Char p -> URec Char p -> Bool)
-> (URec Char p -> URec Char p -> Bool) -> Eq (URec Char p)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall k (p :: k). URec Char p -> URec Char p -> Bool
/= :: URec Char p -> URec Char p -> Bool
$c/= :: forall k (p :: k). URec Char p -> URec Char p -> Bool
== :: URec Char p -> URec Char p -> Bool
$c== :: forall k (p :: k). URec Char p -> URec Char p -> Bool
Eq
, Eq (URec Char p)
Eq (URec Char p)
-> (URec Char p -> URec Char p -> Ordering)
-> (URec Char p -> URec Char p -> Bool)
-> (URec Char p -> URec Char p -> Bool)
-> (URec Char p -> URec Char p -> Bool)
-> (URec Char p -> URec Char p -> Bool)
-> (URec Char p -> URec Char p -> URec Char p)
-> (URec Char p -> URec Char p -> URec Char p)
-> Ord (URec Char p)
URec Char p -> URec Char p -> Bool
URec Char p -> URec Char p -> Ordering
URec Char p -> URec Char p -> URec Char p
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 k (p :: k). Eq (URec Char p)
forall k (p :: k). URec Char p -> URec Char p -> Bool
forall k (p :: k). URec Char p -> URec Char p -> Ordering
forall k (p :: k). URec Char p -> URec Char p -> URec Char p
min :: URec Char p -> URec Char p -> URec Char p
$cmin :: forall k (p :: k). URec Char p -> URec Char p -> URec Char p
max :: URec Char p -> URec Char p -> URec Char p
$cmax :: forall k (p :: k). URec Char p -> URec Char p -> URec Char p
= :: URec Char p -> URec Char p -> Bool $c>= :: forall k (p :: k). URec Char p -> URec Char p -> Bool :: URec Char p -> URec Char p -> Bool $c> :: forall k (p :: k). URec Char p -> URec Char p -> Bool <= :: URec Char p -> URec Char p -> Bool $c<= :: forall k (p :: k). URec Char p -> URec Char p -> Bool < :: URec Char p -> URec Char p -> Bool $c< :: forall k (p :: k). URec Char p -> URec Char p -> Bool compare :: URec Char p -> URec Char p -> Ordering $ccompare :: forall k (p :: k). URec Char p -> URec Char p -> Ordering Ord
, Int -> URec Char p -> ShowS [URec Char p] -> ShowS URec Char p -> String (Int -> URec Char p -> ShowS) -> (URec Char p -> String) -> ([URec Char p] -> ShowS) -> Show (URec Char p) forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a forall k (p :: k). Int -> URec Char p -> ShowS forall k (p :: k). [URec Char p] -> ShowS forall k (p :: k). URec Char p -> String showList :: [URec Char p] -> ShowS $cshowList :: forall k (p :: k). [URec Char p] -> ShowS show :: URec Char p -> String $cshow :: forall k (p :: k). URec Char p -> String showsPrec :: Int -> URec Char p -> ShowS $cshowsPrec :: forall k (p :: k). Int -> URec Char p -> ShowS Show
, (forall a b. (a -> b) -> URec Char a -> URec Char b) -> (forall a b. a -> URec Char b -> URec Char a) -> Functor (URec Char) forall a b. a -> URec Char b -> URec Char a forall a b. (a -> b) -> URec Char a -> URec Char b forall (f :: * -> *). (forall a b. (a -> b) -> f a -> f b) -> (forall a b. a -> f b -> f a) -> Functor f <$ :: forall a b. a -> URec Char b -> URec Char a c<c<c< :: forall a b. a -> URec Char b -> URec Char a fmap :: forall a b. (a -> b) -> URec Char a -> URec Char b $cfmap :: forall a b. (a -> b) -> URec Char a -> URec Char b Functor
, (forall x. URec Char p -> Rep (URec Char p) x) -> (forall x. Rep (URec Char p) x -> URec Char p) -> Generic (URec Char p) forall x. Rep (URec Char p) x -> URec Char p forall x. URec Char p -> Rep (URec Char p) x forall a. (forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a forall k (p :: k) x. Rep (URec Char p) x -> URec Char p forall k (p :: k) x. URec Char p -> Rep (URec Char p) x $cto :: forall k (p :: k) x. Rep (URec Char p) x -> URec Char p $cfrom :: forall k (p :: k) x. URec Char p -> Rep (URec Char p) x Generic
, (forall (a :: k). URec Char a -> Rep1 (URec Char) a) -> (forall (a :: k). Rep1 (URec Char) a -> URec Char a) -> Generic1 (URec Char) forall (a :: k). Rep1 (URec Char) a -> URec Char a forall (a :: k). URec Char a -> Rep1 (URec Char) a forall k (a :: k). Rep1 (URec Char) a -> URec Char a forall k (a :: k). URec Char a -> Rep1 (URec Char) a forall k (f :: k -> *). (forall (a :: k). f a -> Rep1 f a) -> (forall (a :: k). Rep1 f a -> f a) -> Generic1 f $cto1 :: forall k (a :: k). Rep1 (URec Char) a -> URec Char a $cfrom1 :: forall k (a :: k). URec Char a -> Rep1 (URec Char) a Generic1 )
data instance URec Double (p :: k) = UDouble { forall k (p :: k). URec Double p -> Double#
uDouble# :: Double# }
deriving ( URec Double p -> URec Double p -> Bool
(URec Double p -> URec Double p -> Bool)
-> (URec Double p -> URec Double p -> Bool) -> Eq (URec Double p)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall k (p :: k). URec Double p -> URec Double p -> Bool
/= :: URec Double p -> URec Double p -> Bool
$c/= :: forall k (p :: k). URec Double p -> URec Double p -> Bool
== :: URec Double p -> URec Double p -> Bool
$c== :: forall k (p :: k). URec Double p -> URec Double p -> Bool
Eq
, Eq (URec Double p)
Eq (URec Double p)
-> (URec Double p -> URec Double p -> Ordering)
-> (URec Double p -> URec Double p -> Bool)
-> (URec Double p -> URec Double p -> Bool)
-> (URec Double p -> URec Double p -> Bool)
-> (URec Double p -> URec Double p -> Bool)
-> (URec Double p -> URec Double p -> URec Double p)
-> (URec Double p -> URec Double p -> URec Double p)
-> Ord (URec Double p)
URec Double p -> URec Double p -> Bool
URec Double p -> URec Double p -> Ordering
URec Double p -> URec Double p -> URec Double p
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 k (p :: k). Eq (URec Double p)
forall k (p :: k). URec Double p -> URec Double p -> Bool
forall k (p :: k). URec Double p -> URec Double p -> Ordering
forall k (p :: k). URec Double p -> URec Double p -> URec Double p
min :: URec Double p -> URec Double p -> URec Double p
$cmin :: forall k (p :: k). URec Double p -> URec Double p -> URec Double p
max :: URec Double p -> URec Double p -> URec Double p
$cmax :: forall k (p :: k). URec Double p -> URec Double p -> URec Double p
= :: URec Double p -> URec Double p -> Bool $c>= :: forall k (p :: k). URec Double p -> URec Double p -> Bool :: URec Double p -> URec Double p -> Bool $c> :: forall k (p :: k). URec Double p -> URec Double p -> Bool <= :: URec Double p -> URec Double p -> Bool $c<= :: forall k (p :: k). URec Double p -> URec Double p -> Bool < :: URec Double p -> URec Double p -> Bool $c< :: forall k (p :: k). URec Double p -> URec Double p -> Bool compare :: URec Double p -> URec Double p -> Ordering $ccompare :: forall k (p :: k). URec Double p -> URec Double p -> Ordering Ord
, Int -> URec Double p -> ShowS [URec Double p] -> ShowS URec Double p -> String (Int -> URec Double p -> ShowS) -> (URec Double p -> String) -> ([URec Double p] -> ShowS) -> Show (URec Double p) forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a forall k (p :: k). Int -> URec Double p -> ShowS forall k (p :: k). [URec Double p] -> ShowS forall k (p :: k). URec Double p -> String showList :: [URec Double p] -> ShowS $cshowList :: forall k (p :: k). [URec Double p] -> ShowS show :: URec Double p -> String $cshow :: forall k (p :: k). URec Double p -> String showsPrec :: Int -> URec Double p -> ShowS $cshowsPrec :: forall k (p :: k). Int -> URec Double p -> ShowS Show
, (forall a b. (a -> b) -> URec Double a -> URec Double b) -> (forall a b. a -> URec Double b -> URec Double a) -> Functor (URec Double) forall a b. a -> URec Double b -> URec Double a forall a b. (a -> b) -> URec Double a -> URec Double b forall (f :: * -> *). (forall a b. (a -> b) -> f a -> f b) -> (forall a b. a -> f b -> f a) -> Functor f <$ :: forall a b. a -> URec Double b -> URec Double a c<c<c< :: forall a b. a -> URec Double b -> URec Double a fmap :: forall a b. (a -> b) -> URec Double a -> URec Double b $cfmap :: forall a b. (a -> b) -> URec Double a -> URec Double b Functor
, (forall x. URec Double p -> Rep (URec Double p) x) -> (forall x. Rep (URec Double p) x -> URec Double p) -> Generic (URec Double p) forall x. Rep (URec Double p) x -> URec Double p forall x. URec Double p -> Rep (URec Double p) x forall a. (forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a forall k (p :: k) x. Rep (URec Double p) x -> URec Double p forall k (p :: k) x. URec Double p -> Rep (URec Double p) x $cto :: forall k (p :: k) x. Rep (URec Double p) x -> URec Double p $cfrom :: forall k (p :: k) x. URec Double p -> Rep (URec Double p) x Generic
, (forall (a :: k). URec Double a -> Rep1 (URec Double) a) -> (forall (a :: k). Rep1 (URec Double) a -> URec Double a) -> Generic1 (URec Double) forall (a :: k). Rep1 (URec Double) a -> URec Double a forall (a :: k). URec Double a -> Rep1 (URec Double) a forall k (a :: k). Rep1 (URec Double) a -> URec Double a forall k (a :: k). URec Double a -> Rep1 (URec Double) a forall k (f :: k -> *). (forall (a :: k). f a -> Rep1 f a) -> (forall (a :: k). Rep1 f a -> f a) -> Generic1 f $cto1 :: forall k (a :: k). Rep1 (URec Double) a -> URec Double a $cfrom1 :: forall k (a :: k). URec Double a -> Rep1 (URec Double) a Generic1 )
data instance URec Float (p :: k) = UFloat { forall k (p :: k). URec Float p -> Float# uFloat# :: Float# } deriving ( URec Float p -> URec Float p -> Bool (URec Float p -> URec Float p -> Bool) -> (URec Float p -> URec Float p -> Bool) -> Eq (URec Float p) forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a forall k (p :: k). URec Float p -> URec Float p -> Bool /= :: URec Float p -> URec Float p -> Bool $c/= :: forall k (p :: k). URec Float p -> URec Float p -> Bool == :: URec Float p -> URec Float p -> Bool $c== :: forall k (p :: k). URec Float p -> URec Float p -> Bool Eq, Eq (URec Float p) Eq (URec Float p) -> (URec Float p -> URec Float p -> Ordering) -> (URec Float p -> URec Float p -> Bool) -> (URec Float p -> URec Float p -> Bool) -> (URec Float p -> URec Float p -> Bool) -> (URec Float p -> URec Float p -> Bool) -> (URec Float p -> URec Float p -> URec Float p) -> (URec Float p -> URec Float p -> URec Float p) -> Ord (URec Float p) URec Float p -> URec Float p -> Bool URec Float p -> URec Float p -> Ordering URec Float p -> URec Float p -> URec Float p 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 k (p :: k). Eq (URec Float p) forall k (p :: k). URec Float p -> URec Float p -> Bool forall k (p :: k). URec Float p -> URec Float p -> Ordering forall k (p :: k). URec Float p -> URec Float p -> URec Float p min :: URec Float p -> URec Float p -> URec Float p $cmin :: forall k (p :: k). URec Float p -> URec Float p -> URec Float p max :: URec Float p -> URec Float p -> URec Float p $cmax :: forall k (p :: k). URec Float p -> URec Float p -> URec Float p
= :: URec Float p -> URec Float p -> Bool $c>= :: forall k (p :: k). URec Float p -> URec Float p -> Bool :: URec Float p -> URec Float p -> Bool $c> :: forall k (p :: k). URec Float p -> URec Float p -> Bool <= :: URec Float p -> URec Float p -> Bool $c<= :: forall k (p :: k). URec Float p -> URec Float p -> Bool < :: URec Float p -> URec Float p -> Bool $c< :: forall k (p :: k). URec Float p -> URec Float p -> Bool compare :: URec Float p -> URec Float p -> Ordering $ccompare :: forall k (p :: k). URec Float p -> URec Float p -> Ordering Ord, Int -> URec Float p -> ShowS [URec Float p] -> ShowS URec Float p -> String (Int -> URec Float p -> ShowS) -> (URec Float p -> String) -> ([URec Float p] -> ShowS) -> Show (URec Float p) forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a forall k (p :: k). Int -> URec Float p -> ShowS forall k (p :: k). [URec Float p] -> ShowS forall k (p :: k). URec Float p -> String showList :: [URec Float p] -> ShowS $cshowList :: forall k (p :: k). [URec Float p] -> ShowS show :: URec Float p -> String $cshow :: forall k (p :: k). URec Float p -> String showsPrec :: Int -> URec Float p -> ShowS $cshowsPrec :: forall k (p :: k). Int -> URec Float p -> ShowS Show , (forall a b. (a -> b) -> URec Float a -> URec Float b) -> (forall a b. a -> URec Float b -> URec Float a) -> Functor (URec Float) forall a b. a -> URec Float b -> URec Float a forall a b. (a -> b) -> URec Float a -> URec Float b forall (f :: * -> *). (forall a b. (a -> b) -> f a -> f b) -> (forall a b. a -> f b -> f a) -> Functor f <$ :: forall a b. a -> URec Float b -> URec Float a c<c<c< :: forall a b. a -> URec Float b -> URec Float a fmap :: forall a b. (a -> b) -> URec Float a -> URec Float b $cfmap :: forall a b. (a -> b) -> URec Float a -> URec Float b Functor
, (forall x. URec Float p -> Rep (URec Float p) x) -> (forall x. Rep (URec Float p) x -> URec Float p) -> Generic (URec Float p) forall x. Rep (URec Float p) x -> URec Float p forall x. URec Float p -> Rep (URec Float p) x forall a. (forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a forall k (p :: k) x. Rep (URec Float p) x -> URec Float p forall k (p :: k) x. URec Float p -> Rep (URec Float p) x $cto :: forall k (p :: k) x. Rep (URec Float p) x -> URec Float p $cfrom :: forall k (p :: k) x. URec Float p -> Rep (URec Float p) x Generic , (forall (a :: k). URec Float a -> Rep1 (URec Float) a) -> (forall (a :: k). Rep1 (URec Float) a -> URec Float a) -> Generic1 (URec Float) forall (a :: k). Rep1 (URec Float) a -> URec Float a forall (a :: k). URec Float a -> Rep1 (URec Float) a forall k (a :: k). Rep1 (URec Float) a -> URec Float a forall k (a :: k). URec Float a -> Rep1 (URec Float) a forall k (f :: k -> *). (forall (a :: k). f a -> Rep1 f a) -> (forall (a :: k). Rep1 f a -> f a) -> Generic1 f $cto1 :: forall k (a :: k). Rep1 (URec Float) a -> URec Float a $cfrom1 :: forall k (a :: k). URec Float a -> Rep1 (URec Float) a Generic1 )
data instance URec Int (p :: k) = UInt { forall k (p :: k). URec Int p -> Int#
uInt# :: Int# }
deriving ( URec Int p -> URec Int p -> Bool
(URec Int p -> URec Int p -> Bool)
-> (URec Int p -> URec Int p -> Bool) -> Eq (URec Int p)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall k (p :: k). URec Int p -> URec Int p -> Bool
/= :: URec Int p -> URec Int p -> Bool
$c/= :: forall k (p :: k). URec Int p -> URec Int p -> Bool
== :: URec Int p -> URec Int p -> Bool
$c== :: forall k (p :: k). URec Int p -> URec Int p -> Bool
Eq
, Eq (URec Int p)
Eq (URec Int p)
-> (URec Int p -> URec Int p -> Ordering)
-> (URec Int p -> URec Int p -> Bool)
-> (URec Int p -> URec Int p -> Bool)
-> (URec Int p -> URec Int p -> Bool)
-> (URec Int p -> URec Int p -> Bool)
-> (URec Int p -> URec Int p -> URec Int p)
-> (URec Int p -> URec Int p -> URec Int p)
-> Ord (URec Int p)
URec Int p -> URec Int p -> Bool
URec Int p -> URec Int p -> Ordering
URec Int p -> URec Int p -> URec Int p
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 k (p :: k). Eq (URec Int p)
forall k (p :: k). URec Int p -> URec Int p -> Bool
forall k (p :: k). URec Int p -> URec Int p -> Ordering
forall k (p :: k). URec Int p -> URec Int p -> URec Int p
min :: URec Int p -> URec Int p -> URec Int p
$cmin :: forall k (p :: k). URec Int p -> URec Int p -> URec Int p
max :: URec Int p -> URec Int p -> URec Int p
$cmax :: forall k (p :: k). URec Int p -> URec Int p -> URec Int p
= :: URec Int p -> URec Int p -> Bool $c>= :: forall k (p :: k). URec Int p -> URec Int p -> Bool :: URec Int p -> URec Int p -> Bool $c> :: forall k (p :: k). URec Int p -> URec Int p -> Bool <= :: URec Int p -> URec Int p -> Bool $c<= :: forall k (p :: k). URec Int p -> URec Int p -> Bool < :: URec Int p -> URec Int p -> Bool $c< :: forall k (p :: k). URec Int p -> URec Int p -> Bool compare :: URec Int p -> URec Int p -> Ordering $ccompare :: forall k (p :: k). URec Int p -> URec Int p -> Ordering Ord
, Int -> URec Int p -> ShowS [URec Int p] -> ShowS URec Int p -> String (Int -> URec Int p -> ShowS) -> (URec Int p -> String) -> ([URec Int p] -> ShowS) -> Show (URec Int p) forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a forall k (p :: k). Int -> URec Int p -> ShowS forall k (p :: k). [URec Int p] -> ShowS forall k (p :: k). URec Int p -> String showList :: [URec Int p] -> ShowS $cshowList :: forall k (p :: k). [URec Int p] -> ShowS show :: URec Int p -> String $cshow :: forall k (p :: k). URec Int p -> String showsPrec :: Int -> URec Int p -> ShowS $cshowsPrec :: forall k (p :: k). Int -> URec Int p -> ShowS Show
, (forall a b. (a -> b) -> URec Int a -> URec Int b) -> (forall a b. a -> URec Int b -> URec Int a) -> Functor (URec Int) forall a b. a -> URec Int b -> URec Int a forall a b. (a -> b) -> URec Int a -> URec Int b forall (f :: * -> *). (forall a b. (a -> b) -> f a -> f b) -> (forall a b. a -> f b -> f a) -> Functor f <$ :: forall a b. a -> URec Int b -> URec Int a c<c<c< :: forall a b. a -> URec Int b -> URec Int a fmap :: forall a b. (a -> b) -> URec Int a -> URec Int b $cfmap :: forall a b. (a -> b) -> URec Int a -> URec Int b Functor
, (forall x. URec Int p -> Rep (URec Int p) x) -> (forall x. Rep (URec Int p) x -> URec Int p) -> Generic (URec Int p) forall x. Rep (URec Int p) x -> URec Int p forall x. URec Int p -> Rep (URec Int p) x forall a. (forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a forall k (p :: k) x. Rep (URec Int p) x -> URec Int p forall k (p :: k) x. URec Int p -> Rep (URec Int p) x $cto :: forall k (p :: k) x. Rep (URec Int p) x -> URec Int p $cfrom :: forall k (p :: k) x. URec Int p -> Rep (URec Int p) x Generic
, (forall (a :: k). URec Int a -> Rep1 (URec Int) a) -> (forall (a :: k). Rep1 (URec Int) a -> URec Int a) -> Generic1 (URec Int) forall (a :: k). Rep1 (URec Int) a -> URec Int a forall (a :: k). URec Int a -> Rep1 (URec Int) a forall k (a :: k). Rep1 (URec Int) a -> URec Int a forall k (a :: k). URec Int a -> Rep1 (URec Int) a forall k (f :: k -> *). (forall (a :: k). f a -> Rep1 f a) -> (forall (a :: k). Rep1 f a -> f a) -> Generic1 f $cto1 :: forall k (a :: k). Rep1 (URec Int) a -> URec Int a $cfrom1 :: forall k (a :: k). URec Int a -> Rep1 (URec Int) a Generic1 )
data instance URec Word (p :: k) = UWord { forall k (p :: k). URec Word p -> Word#
uWord# :: Word# }
deriving ( URec Word p -> URec Word p -> Bool
(URec Word p -> URec Word p -> Bool)
-> (URec Word p -> URec Word p -> Bool) -> Eq (URec Word p)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall k (p :: k). URec Word p -> URec Word p -> Bool
/= :: URec Word p -> URec Word p -> Bool
$c/= :: forall k (p :: k). URec Word p -> URec Word p -> Bool
== :: URec Word p -> URec Word p -> Bool
$c== :: forall k (p :: k). URec Word p -> URec Word p -> Bool
Eq
, Eq (URec Word p)
Eq (URec Word p)
-> (URec Word p -> URec Word p -> Ordering)
-> (URec Word p -> URec Word p -> Bool)
-> (URec Word p -> URec Word p -> Bool)
-> (URec Word p -> URec Word p -> Bool)
-> (URec Word p -> URec Word p -> Bool)
-> (URec Word p -> URec Word p -> URec Word p)
-> (URec Word p -> URec Word p -> URec Word p)
-> Ord (URec Word p)
URec Word p -> URec Word p -> Bool
URec Word p -> URec Word p -> Ordering
URec Word p -> URec Word p -> URec Word p
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 k (p :: k). Eq (URec Word p)
forall k (p :: k). URec Word p -> URec Word p -> Bool
forall k (p :: k). URec Word p -> URec Word p -> Ordering
forall k (p :: k). URec Word p -> URec Word p -> URec Word p
min :: URec Word p -> URec Word p -> URec Word p
$cmin :: forall k (p :: k). URec Word p -> URec Word p -> URec Word p
max :: URec Word p -> URec Word p -> URec Word p
$cmax :: forall k (p :: k). URec Word p -> URec Word p -> URec Word p
= :: URec Word p -> URec Word p -> Bool $c>= :: forall k (p :: k). URec Word p -> URec Word p -> Bool :: URec Word p -> URec Word p -> Bool $c> :: forall k (p :: k). URec Word p -> URec Word p -> Bool <= :: URec Word p -> URec Word p -> Bool $c<= :: forall k (p :: k). URec Word p -> URec Word p -> Bool < :: URec Word p -> URec Word p -> Bool $c< :: forall k (p :: k). URec Word p -> URec Word p -> Bool compare :: URec Word p -> URec Word p -> Ordering $ccompare :: forall k (p :: k). URec Word p -> URec Word p -> Ordering Ord
, Int -> URec Word p -> ShowS [URec Word p] -> ShowS URec Word p -> String (Int -> URec Word p -> ShowS) -> (URec Word p -> String) -> ([URec Word p] -> ShowS) -> Show (URec Word p) forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a forall k (p :: k). Int -> URec Word p -> ShowS forall k (p :: k). [URec Word p] -> ShowS forall k (p :: k). URec Word p -> String showList :: [URec Word p] -> ShowS $cshowList :: forall k (p :: k). [URec Word p] -> ShowS show :: URec Word p -> String $cshow :: forall k (p :: k). URec Word p -> String showsPrec :: Int -> URec Word p -> ShowS $cshowsPrec :: forall k (p :: k). Int -> URec Word p -> ShowS Show
, (forall a b. (a -> b) -> URec Word a -> URec Word b) -> (forall a b. a -> URec Word b -> URec Word a) -> Functor (URec Word) forall a b. a -> URec Word b -> URec Word a forall a b. (a -> b) -> URec Word a -> URec Word b forall (f :: * -> *). (forall a b. (a -> b) -> f a -> f b) -> (forall a b. a -> f b -> f a) -> Functor f <$ :: forall a b. a -> URec Word b -> URec Word a c<c<c< :: forall a b. a -> URec Word b -> URec Word a fmap :: forall a b. (a -> b) -> URec Word a -> URec Word b $cfmap :: forall a b. (a -> b) -> URec Word a -> URec Word b Functor
, (forall x. URec Word p -> Rep (URec Word p) x) -> (forall x. Rep (URec Word p) x -> URec Word p) -> Generic (URec Word p) forall x. Rep (URec Word p) x -> URec Word p forall x. URec Word p -> Rep (URec Word p) x forall a. (forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a forall k (p :: k) x. Rep (URec Word p) x -> URec Word p forall k (p :: k) x. URec Word p -> Rep (URec Word p) x $cto :: forall k (p :: k) x. Rep (URec Word p) x -> URec Word p $cfrom :: forall k (p :: k) x. URec Word p -> Rep (URec Word p) x Generic
, (forall (a :: k). URec Word a -> Rep1 (URec Word) a) -> (forall (a :: k). Rep1 (URec Word) a -> URec Word a) -> Generic1 (URec Word) forall (a :: k). Rep1 (URec Word) a -> URec Word a forall (a :: k). URec Word a -> Rep1 (URec Word) a forall k (a :: k). Rep1 (URec Word) a -> URec Word a forall k (a :: k). URec Word a -> Rep1 (URec Word) a forall k (f :: k -> *). (forall (a :: k). f a -> Rep1 f a) -> (forall (a :: k). Rep1 f a -> f a) -> Generic1 f $cto1 :: forall k (a :: k). Rep1 (URec Word) a -> URec Word a $cfrom1 :: forall k (a :: k). URec Word a -> Rep1 (URec Word) a Generic1 )
data R
data D
data C
data S
datatypeName :: t d (f :: k -> Type) (a :: k) -> [Char]
moduleName :: t d (f :: k -> Type) (a :: k) -> [Char]
packageName :: t d (f :: k -> Type) (a :: k) -> [Char]
isNewtype :: t d (f :: k -> Type) (a :: k) -> Bool isNewtype t d f a _ = Bool False
instance (KnownSymbol n, KnownSymbol m, KnownSymbol p, SingI nt) => Datatype ('MetaData n m p nt) where datatypeName :: forall k (t :: Meta -> (k -> *) -> k -> *) (f :: k -> *) (a :: k). t ('MetaData n m p nt) f a -> String datatypeName t ('MetaData n m p nt) f a _ = Proxy n -> String forall (n :: Symbol) (proxy :: Symbol -> *). KnownSymbol n => proxy n -> String symbolVal (Proxy n forall {k} (t :: k). Proxy t Proxy :: Proxy n) moduleName :: forall k (t :: Meta -> (k -> *) -> k -> *) (f :: k -> *) (a :: k). t ('MetaData n m p nt) f a -> String moduleName t ('MetaData n m p nt) f a _ = Proxy m -> String forall (n :: Symbol) (proxy :: Symbol -> *). KnownSymbol n => proxy n -> String symbolVal (Proxy m forall {k} (t :: k). Proxy t Proxy :: Proxy m) packageName :: forall k (t :: Meta -> (k -> *) -> k -> *) (f :: k -> *) (a :: k). t ('MetaData n m p nt) f a -> String packageName t ('MetaData n m p nt) f a _ = Proxy p -> String forall (n :: Symbol) (proxy :: Symbol -> *). KnownSymbol n => proxy n -> String symbolVal (Proxy p forall {k} (t :: k). Proxy t Proxy :: Proxy p) isNewtype :: forall k (t :: Meta -> (k -> *) -> k -> *) (f :: k -> *) (a :: k). t ('MetaData n m p nt) f a -> Bool isNewtype t ('MetaData n m p nt) f a _ = Sing nt -> DemoteRep Bool forall k (a :: k). SingKind k => Sing a -> DemoteRep k fromSing (Sing nt forall k (a :: k). SingI a => Sing a sing :: Sing nt)
class Constructor c where
conName :: t c (f :: k -> Type) (a :: k) -> [Char]
conFixity :: t c (f :: k -> Type) (a :: k) -> Fixity conFixity t c f a _ = Fixity Prefix
conIsRecord :: t c (f :: k -> Type) (a :: k) -> Bool conIsRecord t c f a _ = Bool False
instance (KnownSymbol n, SingI f, SingI r) => Constructor ('MetaCons n f r) where conName :: forall k (t :: Meta -> (k -> *) -> k -> *) (f :: k -> *) (a :: k). t ('MetaCons n f r) f a -> String conName t ('MetaCons n f r) f a _ = Proxy n -> String forall (n :: Symbol) (proxy :: Symbol -> *). KnownSymbol n => proxy n -> String symbolVal (Proxy n forall {k} (t :: k). Proxy t Proxy :: Proxy n) conFixity :: forall k (t :: Meta -> (k -> *) -> k -> *) (f :: k -> *) (a :: k). t ('MetaCons n f r) f a -> Fixity conFixity t ('MetaCons n f r) f a _ = Sing f -> DemoteRep FixityI forall k (a :: k). SingKind k => Sing a -> DemoteRep k fromSing (Sing f forall k (a :: k). SingI a => Sing a sing :: Sing f) conIsRecord :: forall k (t :: Meta -> (k -> *) -> k -> *) (f :: k -> *) (a :: k). t ('MetaCons n f r) f a -> Bool conIsRecord t ('MetaCons n f r) f a _ = Sing r -> DemoteRep Bool forall k (a :: k). SingKind k => Sing a -> DemoteRep k fromSing (Sing r forall k (a :: k). SingI a => Sing a sing :: Sing r)
data Fixity = Prefix | Infix Associativity Int
deriving ( Fixity -> Fixity -> Bool
(Fixity -> Fixity -> Bool)
-> (Fixity -> Fixity -> Bool) -> Eq Fixity
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Fixity -> Fixity -> Bool
$c/= :: Fixity -> Fixity -> Bool
== :: Fixity -> Fixity -> Bool
$c== :: Fixity -> Fixity -> Bool
Eq
, Int -> Fixity -> ShowS
[Fixity] -> ShowS
Fixity -> String
(Int -> Fixity -> ShowS)
-> (Fixity -> String) -> ([Fixity] -> ShowS) -> Show Fixity
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Fixity] -> ShowS
$cshowList :: [Fixity] -> ShowS
show :: Fixity -> String
$cshow :: Fixity -> String
showsPrec :: Int -> Fixity -> ShowS
$cshowsPrec :: Int -> Fixity -> ShowS
Show
, Eq Fixity
Eq Fixity
-> (Fixity -> Fixity -> Ordering)
-> (Fixity -> Fixity -> Bool)
-> (Fixity -> Fixity -> Bool)
-> (Fixity -> Fixity -> Bool)
-> (Fixity -> Fixity -> Bool)
-> (Fixity -> Fixity -> Fixity)
-> (Fixity -> Fixity -> Fixity)
-> Ord Fixity
Fixity -> Fixity -> Bool
Fixity -> Fixity -> Ordering
Fixity -> Fixity -> Fixity
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
min :: Fixity -> Fixity -> Fixity
$cmin :: Fixity -> Fixity -> Fixity
max :: Fixity -> Fixity -> Fixity
$cmax :: Fixity -> Fixity -> Fixity
= :: Fixity -> Fixity -> Bool $c>= :: Fixity -> Fixity -> Bool :: Fixity -> Fixity -> Bool $c> :: Fixity -> Fixity -> Bool <= :: Fixity -> Fixity -> Bool $c<= :: Fixity -> Fixity -> Bool < :: Fixity -> Fixity -> Bool $c< :: Fixity -> Fixity -> Bool compare :: Fixity -> Fixity -> Ordering $ccompare :: Fixity -> Fixity -> Ordering Ord
, ReadPrec [Fixity] ReadPrec Fixity Int -> ReadS Fixity ReadS [Fixity] (Int -> ReadS Fixity) -> ReadS [Fixity] -> ReadPrec Fixity -> ReadPrec [Fixity] -> Read Fixity forall a. (Int -> ReadS a) -> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a readListPrec :: ReadPrec [Fixity] $creadListPrec :: ReadPrec [Fixity] readPrec :: ReadPrec Fixity $creadPrec :: ReadPrec Fixity readList :: ReadS [Fixity] $creadList :: ReadS [Fixity] readsPrec :: Int -> ReadS Fixity $creadsPrec :: Int -> ReadS Fixity Read
, (forall x. Fixity -> Rep Fixity x) -> (forall x. Rep Fixity x -> Fixity) -> Generic Fixity forall x. Rep Fixity x -> Fixity forall x. Fixity -> Rep Fixity x forall a. (forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a $cto :: forall x. Rep Fixity x -> Fixity $cfrom :: forall x. Fixity -> Rep Fixity x Generic
)
data FixityI = PrefixI | InfixI Associativity Nat
prec :: Fixity -> Int prec :: Fixity -> Int prec Fixity Prefix = Int 10 prec (Infix Associativity _ Int n) = Int n
data Associativity = LeftAssociative
| RightAssociative
| NotAssociative
deriving ( Associativity -> Associativity -> Bool
(Associativity -> Associativity -> Bool)
-> (Associativity -> Associativity -> Bool) -> Eq Associativity
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Associativity -> Associativity -> Bool
$c/= :: Associativity -> Associativity -> Bool
== :: Associativity -> Associativity -> Bool
$c== :: Associativity -> Associativity -> Bool
Eq
, Int -> Associativity -> ShowS
[Associativity] -> ShowS
Associativity -> String
(Int -> Associativity -> ShowS)
-> (Associativity -> String)
-> ([Associativity] -> ShowS)
-> Show Associativity
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Associativity] -> ShowS
$cshowList :: [Associativity] -> ShowS
show :: Associativity -> String
$cshow :: Associativity -> String
showsPrec :: Int -> Associativity -> ShowS
$cshowsPrec :: Int -> Associativity -> ShowS
Show
, Eq Associativity
Eq Associativity
-> (Associativity -> Associativity -> Ordering)
-> (Associativity -> Associativity -> Bool)
-> (Associativity -> Associativity -> Bool)
-> (Associativity -> Associativity -> Bool)
-> (Associativity -> Associativity -> Bool)
-> (Associativity -> Associativity -> Associativity)
-> (Associativity -> Associativity -> Associativity)
-> Ord Associativity
Associativity -> Associativity -> Bool
Associativity -> Associativity -> Ordering
Associativity -> Associativity -> Associativity
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
min :: Associativity -> Associativity -> Associativity
$cmin :: Associativity -> Associativity -> Associativity
max :: Associativity -> Associativity -> Associativity
$cmax :: Associativity -> Associativity -> Associativity
= :: Associativity -> Associativity -> Bool $c>= :: Associativity -> Associativity -> Bool :: Associativity -> Associativity -> Bool $c> :: Associativity -> Associativity -> Bool <= :: Associativity -> Associativity -> Bool $c<= :: Associativity -> Associativity -> Bool < :: Associativity -> Associativity -> Bool $c< :: Associativity -> Associativity -> Bool compare :: Associativity -> Associativity -> Ordering $ccompare :: Associativity -> Associativity -> Ordering Ord
, ReadPrec [Associativity] ReadPrec Associativity Int -> ReadS Associativity ReadS [Associativity] (Int -> ReadS Associativity) -> ReadS [Associativity] -> ReadPrec Associativity -> ReadPrec [Associativity] -> Read Associativity forall a. (Int -> ReadS a) -> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a readListPrec :: ReadPrec [Associativity] $creadListPrec :: ReadPrec [Associativity] readPrec :: ReadPrec Associativity $creadPrec :: ReadPrec Associativity readList :: ReadS [Associativity] $creadList :: ReadS [Associativity] readsPrec :: Int -> ReadS Associativity $creadsPrec :: Int -> ReadS Associativity Read
, Int -> Associativity Associativity -> Int Associativity -> [Associativity] Associativity -> Associativity Associativity -> Associativity -> [Associativity] Associativity -> Associativity -> Associativity -> [Associativity] (Associativity -> Associativity) -> (Associativity -> Associativity) -> (Int -> Associativity) -> (Associativity -> Int) -> (Associativity -> [Associativity]) -> (Associativity -> Associativity -> [Associativity]) -> (Associativity -> Associativity -> [Associativity]) -> (Associativity -> Associativity -> Associativity -> [Associativity]) -> Enum Associativity forall a. (a -> a) -> (a -> a) -> (Int -> a) -> (a -> Int) -> (a -> [a]) -> (a -> a -> [a]) -> (a -> a -> [a]) -> (a -> a -> a -> [a]) -> Enum a enumFromThenTo :: Associativity -> Associativity -> Associativity -> [Associativity] $cenumFromThenTo :: Associativity -> Associativity -> Associativity -> [Associativity] enumFromTo :: Associativity -> Associativity -> [Associativity] $cenumFromTo :: Associativity -> Associativity -> [Associativity] enumFromThen :: Associativity -> Associativity -> [Associativity] $cenumFromThen :: Associativity -> Associativity -> [Associativity] enumFrom :: Associativity -> [Associativity] $cenumFrom :: Associativity -> [Associativity] fromEnum :: Associativity -> Int $cfromEnum :: Associativity -> Int toEnum :: Int -> Associativity $ctoEnum :: Int -> Associativity pred :: Associativity -> Associativity $cpred :: Associativity -> Associativity succ :: Associativity -> Associativity $csucc :: Associativity -> Associativity Enum
, Associativity Associativity -> Associativity -> Bounded Associativity forall a. a -> a -> Bounded a maxBound :: Associativity $cmaxBound :: Associativity minBound :: Associativity $cminBound :: Associativity Bounded
, Ord Associativity Ord Associativity -> ((Associativity, Associativity) -> [Associativity]) -> ((Associativity, Associativity) -> Associativity -> Int) -> ((Associativity, Associativity) -> Associativity -> Int) -> ((Associativity, Associativity) -> Associativity -> Bool) -> ((Associativity, Associativity) -> Int) -> ((Associativity, Associativity) -> Int) -> Ix Associativity (Associativity, Associativity) -> Int (Associativity, Associativity) -> [Associativity] (Associativity, Associativity) -> Associativity -> Bool (Associativity, Associativity) -> Associativity -> Int forall a. Ord a -> ((a, a) -> [a]) -> ((a, a) -> a -> Int) -> ((a, a) -> a -> Int) -> ((a, a) -> a -> Bool) -> ((a, a) -> Int) -> ((a, a) -> Int) -> Ix a unsafeRangeSize :: (Associativity, Associativity) -> Int $cunsafeRangeSize :: (Associativity, Associativity) -> Int rangeSize :: (Associativity, Associativity) -> Int $crangeSize :: (Associativity, Associativity) -> Int inRange :: (Associativity, Associativity) -> Associativity -> Bool $cinRange :: (Associativity, Associativity) -> Associativity -> Bool unsafeIndex :: (Associativity, Associativity) -> Associativity -> Int $cunsafeIndex :: (Associativity, Associativity) -> Associativity -> Int index :: (Associativity, Associativity) -> Associativity -> Int $cindex :: (Associativity, Associativity) -> Associativity -> Int range :: (Associativity, Associativity) -> [Associativity] $crange :: (Associativity, Associativity) -> [Associativity] Ix
, (forall x. Associativity -> Rep Associativity x) -> (forall x. Rep Associativity x -> Associativity) -> Generic Associativity forall x. Rep Associativity x -> Associativity forall x. Associativity -> Rep Associativity x forall a. (forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a $cto :: forall x. Rep Associativity x -> Associativity $cfrom :: forall x. Associativity -> Rep Associativity x Generic
)
data SourceUnpackedness = NoSourceUnpackedness
| SourceNoUnpack
| SourceUnpack
deriving ( SourceUnpackedness -> SourceUnpackedness -> Bool
(SourceUnpackedness -> SourceUnpackedness -> Bool)
-> (SourceUnpackedness -> SourceUnpackedness -> Bool)
-> Eq SourceUnpackedness
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SourceUnpackedness -> SourceUnpackedness -> Bool
$c/= :: SourceUnpackedness -> SourceUnpackedness -> Bool
== :: SourceUnpackedness -> SourceUnpackedness -> Bool
$c== :: SourceUnpackedness -> SourceUnpackedness -> Bool
Eq
, Int -> SourceUnpackedness -> ShowS
[SourceUnpackedness] -> ShowS
SourceUnpackedness -> String
(Int -> SourceUnpackedness -> ShowS)
-> (SourceUnpackedness -> String)
-> ([SourceUnpackedness] -> ShowS)
-> Show SourceUnpackedness
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SourceUnpackedness] -> ShowS
$cshowList :: [SourceUnpackedness] -> ShowS
show :: SourceUnpackedness -> String
$cshow :: SourceUnpackedness -> String
showsPrec :: Int -> SourceUnpackedness -> ShowS
$cshowsPrec :: Int -> SourceUnpackedness -> ShowS
Show
, Eq SourceUnpackedness
Eq SourceUnpackedness
-> (SourceUnpackedness -> SourceUnpackedness -> Ordering)
-> (SourceUnpackedness -> SourceUnpackedness -> Bool)
-> (SourceUnpackedness -> SourceUnpackedness -> Bool)
-> (SourceUnpackedness -> SourceUnpackedness -> Bool)
-> (SourceUnpackedness -> SourceUnpackedness -> Bool)
-> (SourceUnpackedness -> SourceUnpackedness -> SourceUnpackedness)
-> (SourceUnpackedness -> SourceUnpackedness -> SourceUnpackedness)
-> Ord SourceUnpackedness
SourceUnpackedness -> SourceUnpackedness -> Bool
SourceUnpackedness -> SourceUnpackedness -> Ordering
SourceUnpackedness -> SourceUnpackedness -> SourceUnpackedness
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
min :: SourceUnpackedness -> SourceUnpackedness -> SourceUnpackedness
$cmin :: SourceUnpackedness -> SourceUnpackedness -> SourceUnpackedness
max :: SourceUnpackedness -> SourceUnpackedness -> SourceUnpackedness
$cmax :: SourceUnpackedness -> SourceUnpackedness -> SourceUnpackedness
= :: SourceUnpackedness -> SourceUnpackedness -> Bool $c>= :: SourceUnpackedness -> SourceUnpackedness -> Bool :: SourceUnpackedness -> SourceUnpackedness -> Bool $c> :: SourceUnpackedness -> SourceUnpackedness -> Bool <= :: SourceUnpackedness -> SourceUnpackedness -> Bool $c<= :: SourceUnpackedness -> SourceUnpackedness -> Bool < :: SourceUnpackedness -> SourceUnpackedness -> Bool $c< :: SourceUnpackedness -> SourceUnpackedness -> Bool compare :: SourceUnpackedness -> SourceUnpackedness -> Ordering $ccompare :: SourceUnpackedness -> SourceUnpackedness -> Ordering Ord
, ReadPrec [SourceUnpackedness] ReadPrec SourceUnpackedness Int -> ReadS SourceUnpackedness ReadS [SourceUnpackedness] (Int -> ReadS SourceUnpackedness) -> ReadS [SourceUnpackedness] -> ReadPrec SourceUnpackedness -> ReadPrec [SourceUnpackedness] -> Read SourceUnpackedness forall a. (Int -> ReadS a) -> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a readListPrec :: ReadPrec [SourceUnpackedness] $creadListPrec :: ReadPrec [SourceUnpackedness] readPrec :: ReadPrec SourceUnpackedness $creadPrec :: ReadPrec SourceUnpackedness readList :: ReadS [SourceUnpackedness] $creadList :: ReadS [SourceUnpackedness] readsPrec :: Int -> ReadS SourceUnpackedness $creadsPrec :: Int -> ReadS SourceUnpackedness Read
, Int -> SourceUnpackedness SourceUnpackedness -> Int SourceUnpackedness -> [SourceUnpackedness] SourceUnpackedness -> SourceUnpackedness SourceUnpackedness -> SourceUnpackedness -> [SourceUnpackedness] SourceUnpackedness -> SourceUnpackedness -> SourceUnpackedness -> [SourceUnpackedness] (SourceUnpackedness -> SourceUnpackedness) -> (SourceUnpackedness -> SourceUnpackedness) -> (Int -> SourceUnpackedness) -> (SourceUnpackedness -> Int) -> (SourceUnpackedness -> [SourceUnpackedness]) -> (SourceUnpackedness -> SourceUnpackedness -> [SourceUnpackedness]) -> (SourceUnpackedness -> SourceUnpackedness -> [SourceUnpackedness]) -> (SourceUnpackedness -> SourceUnpackedness -> SourceUnpackedness -> [SourceUnpackedness]) -> Enum SourceUnpackedness forall a. (a -> a) -> (a -> a) -> (Int -> a) -> (a -> Int) -> (a -> [a]) -> (a -> a -> [a]) -> (a -> a -> [a]) -> (a -> a -> a -> [a]) -> Enum a enumFromThenTo :: SourceUnpackedness -> SourceUnpackedness -> SourceUnpackedness -> [SourceUnpackedness] $cenumFromThenTo :: SourceUnpackedness -> SourceUnpackedness -> SourceUnpackedness -> [SourceUnpackedness] enumFromTo :: SourceUnpackedness -> SourceUnpackedness -> [SourceUnpackedness] $cenumFromTo :: SourceUnpackedness -> SourceUnpackedness -> [SourceUnpackedness] enumFromThen :: SourceUnpackedness -> SourceUnpackedness -> [SourceUnpackedness] $cenumFromThen :: SourceUnpackedness -> SourceUnpackedness -> [SourceUnpackedness] enumFrom :: SourceUnpackedness -> [SourceUnpackedness] $cenumFrom :: SourceUnpackedness -> [SourceUnpackedness] fromEnum :: SourceUnpackedness -> Int $cfromEnum :: SourceUnpackedness -> Int toEnum :: Int -> SourceUnpackedness $ctoEnum :: Int -> SourceUnpackedness pred :: SourceUnpackedness -> SourceUnpackedness $cpred :: SourceUnpackedness -> SourceUnpackedness succ :: SourceUnpackedness -> SourceUnpackedness $csucc :: SourceUnpackedness -> SourceUnpackedness Enum
, SourceUnpackedness SourceUnpackedness -> SourceUnpackedness -> Bounded SourceUnpackedness forall a. a -> a -> Bounded a maxBound :: SourceUnpackedness $cmaxBound :: SourceUnpackedness minBound :: SourceUnpackedness $cminBound :: SourceUnpackedness Bounded , Ord SourceUnpackedness Ord SourceUnpackedness -> ((SourceUnpackedness, SourceUnpackedness) -> [SourceUnpackedness]) -> ((SourceUnpackedness, SourceUnpackedness) -> SourceUnpackedness -> Int) -> ((SourceUnpackedness, SourceUnpackedness) -> SourceUnpackedness -> Int) -> ((SourceUnpackedness, SourceUnpackedness) -> SourceUnpackedness -> Bool) -> ((SourceUnpackedness, SourceUnpackedness) -> Int) -> ((SourceUnpackedness, SourceUnpackedness) -> Int) -> Ix SourceUnpackedness (SourceUnpackedness, SourceUnpackedness) -> Int (SourceUnpackedness, SourceUnpackedness) -> [SourceUnpackedness] (SourceUnpackedness, SourceUnpackedness) -> SourceUnpackedness -> Bool (SourceUnpackedness, SourceUnpackedness) -> SourceUnpackedness -> Int forall a. Ord a -> ((a, a) -> [a]) -> ((a, a) -> a -> Int) -> ((a, a) -> a -> Int) -> ((a, a) -> a -> Bool) -> ((a, a) -> Int) -> ((a, a) -> Int) -> Ix a unsafeRangeSize :: (SourceUnpackedness, SourceUnpackedness) -> Int $cunsafeRangeSize :: (SourceUnpackedness, SourceUnpackedness) -> Int rangeSize :: (SourceUnpackedness, SourceUnpackedness) -> Int $crangeSize :: (SourceUnpackedness, SourceUnpackedness) -> Int inRange :: (SourceUnpackedness, SourceUnpackedness) -> SourceUnpackedness -> Bool $cinRange :: (SourceUnpackedness, SourceUnpackedness) -> SourceUnpackedness -> Bool unsafeIndex :: (SourceUnpackedness, SourceUnpackedness) -> SourceUnpackedness -> Int $cunsafeIndex :: (SourceUnpackedness, SourceUnpackedness) -> SourceUnpackedness -> Int index :: (SourceUnpackedness, SourceUnpackedness) -> SourceUnpackedness -> Int $cindex :: (SourceUnpackedness, SourceUnpackedness) -> SourceUnpackedness -> Int range :: (SourceUnpackedness, SourceUnpackedness) -> [SourceUnpackedness] $crange :: (SourceUnpackedness, SourceUnpackedness) -> [SourceUnpackedness] Ix
, (forall x. SourceUnpackedness -> Rep SourceUnpackedness x) -> (forall x. Rep SourceUnpackedness x -> SourceUnpackedness) -> Generic SourceUnpackedness forall x. Rep SourceUnpackedness x -> SourceUnpackedness forall x. SourceUnpackedness -> Rep SourceUnpackedness x forall a. (forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a $cto :: forall x. Rep SourceUnpackedness x -> SourceUnpackedness $cfrom :: forall x. SourceUnpackedness -> Rep SourceUnpackedness x Generic )
data SourceStrictness = NoSourceStrictness
| SourceLazy
| SourceStrict
deriving ( SourceStrictness -> SourceStrictness -> Bool
(SourceStrictness -> SourceStrictness -> Bool)
-> (SourceStrictness -> SourceStrictness -> Bool)
-> Eq SourceStrictness
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SourceStrictness -> SourceStrictness -> Bool
$c/= :: SourceStrictness -> SourceStrictness -> Bool
== :: SourceStrictness -> SourceStrictness -> Bool
$c== :: SourceStrictness -> SourceStrictness -> Bool
Eq
, Int -> SourceStrictness -> ShowS
[SourceStrictness] -> ShowS
SourceStrictness -> String
(Int -> SourceStrictness -> ShowS)
-> (SourceStrictness -> String)
-> ([SourceStrictness] -> ShowS)
-> Show SourceStrictness
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SourceStrictness] -> ShowS
$cshowList :: [SourceStrictness] -> ShowS
show :: SourceStrictness -> String
$cshow :: SourceStrictness -> String
showsPrec :: Int -> SourceStrictness -> ShowS
$cshowsPrec :: Int -> SourceStrictness -> ShowS
Show
, Eq SourceStrictness
Eq SourceStrictness
-> (SourceStrictness -> SourceStrictness -> Ordering)
-> (SourceStrictness -> SourceStrictness -> Bool)
-> (SourceStrictness -> SourceStrictness -> Bool)
-> (SourceStrictness -> SourceStrictness -> Bool)
-> (SourceStrictness -> SourceStrictness -> Bool)
-> (SourceStrictness -> SourceStrictness -> SourceStrictness)
-> (SourceStrictness -> SourceStrictness -> SourceStrictness)
-> Ord SourceStrictness
SourceStrictness -> SourceStrictness -> Bool
SourceStrictness -> SourceStrictness -> Ordering
SourceStrictness -> SourceStrictness -> SourceStrictness
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
min :: SourceStrictness -> SourceStrictness -> SourceStrictness
$cmin :: SourceStrictness -> SourceStrictness -> SourceStrictness
max :: SourceStrictness -> SourceStrictness -> SourceStrictness
$cmax :: SourceStrictness -> SourceStrictness -> SourceStrictness
= :: SourceStrictness -> SourceStrictness -> Bool $c>= :: SourceStrictness -> SourceStrictness -> Bool :: SourceStrictness -> SourceStrictness -> Bool $c> :: SourceStrictness -> SourceStrictness -> Bool <= :: SourceStrictness -> SourceStrictness -> Bool $c<= :: SourceStrictness -> SourceStrictness -> Bool < :: SourceStrictness -> SourceStrictness -> Bool $c< :: SourceStrictness -> SourceStrictness -> Bool compare :: SourceStrictness -> SourceStrictness -> Ordering $ccompare :: SourceStrictness -> SourceStrictness -> Ordering Ord
, ReadPrec [SourceStrictness] ReadPrec SourceStrictness Int -> ReadS SourceStrictness ReadS [SourceStrictness] (Int -> ReadS SourceStrictness) -> ReadS [SourceStrictness] -> ReadPrec SourceStrictness -> ReadPrec [SourceStrictness] -> Read SourceStrictness forall a. (Int -> ReadS a) -> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a readListPrec :: ReadPrec [SourceStrictness] $creadListPrec :: ReadPrec [SourceStrictness] readPrec :: ReadPrec SourceStrictness $creadPrec :: ReadPrec SourceStrictness readList :: ReadS [SourceStrictness] $creadList :: ReadS [SourceStrictness] readsPrec :: Int -> ReadS SourceStrictness $creadsPrec :: Int -> ReadS SourceStrictness Read
, Int -> SourceStrictness SourceStrictness -> Int SourceStrictness -> [SourceStrictness] SourceStrictness -> SourceStrictness SourceStrictness -> SourceStrictness -> [SourceStrictness] SourceStrictness -> SourceStrictness -> SourceStrictness -> [SourceStrictness] (SourceStrictness -> SourceStrictness) -> (SourceStrictness -> SourceStrictness) -> (Int -> SourceStrictness) -> (SourceStrictness -> Int) -> (SourceStrictness -> [SourceStrictness]) -> (SourceStrictness -> SourceStrictness -> [SourceStrictness]) -> (SourceStrictness -> SourceStrictness -> [SourceStrictness]) -> (SourceStrictness -> SourceStrictness -> SourceStrictness -> [SourceStrictness]) -> Enum SourceStrictness forall a. (a -> a) -> (a -> a) -> (Int -> a) -> (a -> Int) -> (a -> [a]) -> (a -> a -> [a]) -> (a -> a -> [a]) -> (a -> a -> a -> [a]) -> Enum a enumFromThenTo :: SourceStrictness -> SourceStrictness -> SourceStrictness -> [SourceStrictness] $cenumFromThenTo :: SourceStrictness -> SourceStrictness -> SourceStrictness -> [SourceStrictness] enumFromTo :: SourceStrictness -> SourceStrictness -> [SourceStrictness] $cenumFromTo :: SourceStrictness -> SourceStrictness -> [SourceStrictness] enumFromThen :: SourceStrictness -> SourceStrictness -> [SourceStrictness] $cenumFromThen :: SourceStrictness -> SourceStrictness -> [SourceStrictness] enumFrom :: SourceStrictness -> [SourceStrictness] $cenumFrom :: SourceStrictness -> [SourceStrictness] fromEnum :: SourceStrictness -> Int $cfromEnum :: SourceStrictness -> Int toEnum :: Int -> SourceStrictness $ctoEnum :: Int -> SourceStrictness pred :: SourceStrictness -> SourceStrictness $cpred :: SourceStrictness -> SourceStrictness succ :: SourceStrictness -> SourceStrictness $csucc :: SourceStrictness -> SourceStrictness Enum
, SourceStrictness SourceStrictness -> SourceStrictness -> Bounded SourceStrictness forall a. a -> a -> Bounded a maxBound :: SourceStrictness $cmaxBound :: SourceStrictness minBound :: SourceStrictness $cminBound :: SourceStrictness Bounded , Ord SourceStrictness Ord SourceStrictness -> ((SourceStrictness, SourceStrictness) -> [SourceStrictness]) -> ((SourceStrictness, SourceStrictness) -> SourceStrictness -> Int) -> ((SourceStrictness, SourceStrictness) -> SourceStrictness -> Int) -> ((SourceStrictness, SourceStrictness) -> SourceStrictness -> Bool) -> ((SourceStrictness, SourceStrictness) -> Int) -> ((SourceStrictness, SourceStrictness) -> Int) -> Ix SourceStrictness (SourceStrictness, SourceStrictness) -> Int (SourceStrictness, SourceStrictness) -> [SourceStrictness] (SourceStrictness, SourceStrictness) -> SourceStrictness -> Bool (SourceStrictness, SourceStrictness) -> SourceStrictness -> Int forall a. Ord a -> ((a, a) -> [a]) -> ((a, a) -> a -> Int) -> ((a, a) -> a -> Int) -> ((a, a) -> a -> Bool) -> ((a, a) -> Int) -> ((a, a) -> Int) -> Ix a unsafeRangeSize :: (SourceStrictness, SourceStrictness) -> Int $cunsafeRangeSize :: (SourceStrictness, SourceStrictness) -> Int rangeSize :: (SourceStrictness, SourceStrictness) -> Int $crangeSize :: (SourceStrictness, SourceStrictness) -> Int inRange :: (SourceStrictness, SourceStrictness) -> SourceStrictness -> Bool $cinRange :: (SourceStrictness, SourceStrictness) -> SourceStrictness -> Bool unsafeIndex :: (SourceStrictness, SourceStrictness) -> SourceStrictness -> Int $cunsafeIndex :: (SourceStrictness, SourceStrictness) -> SourceStrictness -> Int index :: (SourceStrictness, SourceStrictness) -> SourceStrictness -> Int $cindex :: (SourceStrictness, SourceStrictness) -> SourceStrictness -> Int range :: (SourceStrictness, SourceStrictness) -> [SourceStrictness] $crange :: (SourceStrictness, SourceStrictness) -> [SourceStrictness] Ix
, (forall x. SourceStrictness -> Rep SourceStrictness x) -> (forall x. Rep SourceStrictness x -> SourceStrictness) -> Generic SourceStrictness forall x. Rep SourceStrictness x -> SourceStrictness forall x. SourceStrictness -> Rep SourceStrictness x forall a. (forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a $cto :: forall x. Rep SourceStrictness x -> SourceStrictness $cfrom :: forall x. SourceStrictness -> Rep SourceStrictness x Generic )
data DecidedStrictness = DecidedLazy
| DecidedStrict
| DecidedUnpack
deriving ( DecidedStrictness -> DecidedStrictness -> Bool
(DecidedStrictness -> DecidedStrictness -> Bool)
-> (DecidedStrictness -> DecidedStrictness -> Bool)
-> Eq DecidedStrictness
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DecidedStrictness -> DecidedStrictness -> Bool
$c/= :: DecidedStrictness -> DecidedStrictness -> Bool
== :: DecidedStrictness -> DecidedStrictness -> Bool
$c== :: DecidedStrictness -> DecidedStrictness -> Bool
Eq
, Int -> DecidedStrictness -> ShowS
[DecidedStrictness] -> ShowS
DecidedStrictness -> String
(Int -> DecidedStrictness -> ShowS)
-> (DecidedStrictness -> String)
-> ([DecidedStrictness] -> ShowS)
-> Show DecidedStrictness
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DecidedStrictness] -> ShowS
$cshowList :: [DecidedStrictness] -> ShowS
show :: DecidedStrictness -> String
$cshow :: DecidedStrictness -> String
showsPrec :: Int -> DecidedStrictness -> ShowS
$cshowsPrec :: Int -> DecidedStrictness -> ShowS
Show
, Eq DecidedStrictness
Eq DecidedStrictness
-> (DecidedStrictness -> DecidedStrictness -> Ordering)
-> (DecidedStrictness -> DecidedStrictness -> Bool)
-> (DecidedStrictness -> DecidedStrictness -> Bool)
-> (DecidedStrictness -> DecidedStrictness -> Bool)
-> (DecidedStrictness -> DecidedStrictness -> Bool)
-> (DecidedStrictness -> DecidedStrictness -> DecidedStrictness)
-> (DecidedStrictness -> DecidedStrictness -> DecidedStrictness)
-> Ord DecidedStrictness
DecidedStrictness -> DecidedStrictness -> Bool
DecidedStrictness -> DecidedStrictness -> Ordering
DecidedStrictness -> DecidedStrictness -> DecidedStrictness
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
min :: DecidedStrictness -> DecidedStrictness -> DecidedStrictness
$cmin :: DecidedStrictness -> DecidedStrictness -> DecidedStrictness
max :: DecidedStrictness -> DecidedStrictness -> DecidedStrictness
$cmax :: DecidedStrictness -> DecidedStrictness -> DecidedStrictness
= :: DecidedStrictness -> DecidedStrictness -> Bool $c>= :: DecidedStrictness -> DecidedStrictness -> Bool :: DecidedStrictness -> DecidedStrictness -> Bool $c> :: DecidedStrictness -> DecidedStrictness -> Bool <= :: DecidedStrictness -> DecidedStrictness -> Bool $c<= :: DecidedStrictness -> DecidedStrictness -> Bool < :: DecidedStrictness -> DecidedStrictness -> Bool $c< :: DecidedStrictness -> DecidedStrictness -> Bool compare :: DecidedStrictness -> DecidedStrictness -> Ordering $ccompare :: DecidedStrictness -> DecidedStrictness -> Ordering Ord
, ReadPrec [DecidedStrictness] ReadPrec DecidedStrictness Int -> ReadS DecidedStrictness ReadS [DecidedStrictness] (Int -> ReadS DecidedStrictness) -> ReadS [DecidedStrictness] -> ReadPrec DecidedStrictness -> ReadPrec [DecidedStrictness] -> Read DecidedStrictness forall a. (Int -> ReadS a) -> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a readListPrec :: ReadPrec [DecidedStrictness] $creadListPrec :: ReadPrec [DecidedStrictness] readPrec :: ReadPrec DecidedStrictness $creadPrec :: ReadPrec DecidedStrictness readList :: ReadS [DecidedStrictness] $creadList :: ReadS [DecidedStrictness] readsPrec :: Int -> ReadS DecidedStrictness $creadsPrec :: Int -> ReadS DecidedStrictness Read
, Int -> DecidedStrictness DecidedStrictness -> Int DecidedStrictness -> [DecidedStrictness] DecidedStrictness -> DecidedStrictness DecidedStrictness -> DecidedStrictness -> [DecidedStrictness] DecidedStrictness -> DecidedStrictness -> DecidedStrictness -> [DecidedStrictness] (DecidedStrictness -> DecidedStrictness) -> (DecidedStrictness -> DecidedStrictness) -> (Int -> DecidedStrictness) -> (DecidedStrictness -> Int) -> (DecidedStrictness -> [DecidedStrictness]) -> (DecidedStrictness -> DecidedStrictness -> [DecidedStrictness]) -> (DecidedStrictness -> DecidedStrictness -> [DecidedStrictness]) -> (DecidedStrictness -> DecidedStrictness -> DecidedStrictness -> [DecidedStrictness]) -> Enum DecidedStrictness forall a. (a -> a) -> (a -> a) -> (Int -> a) -> (a -> Int) -> (a -> [a]) -> (a -> a -> [a]) -> (a -> a -> [a]) -> (a -> a -> a -> [a]) -> Enum a enumFromThenTo :: DecidedStrictness -> DecidedStrictness -> DecidedStrictness -> [DecidedStrictness] $cenumFromThenTo :: DecidedStrictness -> DecidedStrictness -> DecidedStrictness -> [DecidedStrictness] enumFromTo :: DecidedStrictness -> DecidedStrictness -> [DecidedStrictness] $cenumFromTo :: DecidedStrictness -> DecidedStrictness -> [DecidedStrictness] enumFromThen :: DecidedStrictness -> DecidedStrictness -> [DecidedStrictness] $cenumFromThen :: DecidedStrictness -> DecidedStrictness -> [DecidedStrictness] enumFrom :: DecidedStrictness -> [DecidedStrictness] $cenumFrom :: DecidedStrictness -> [DecidedStrictness] fromEnum :: DecidedStrictness -> Int $cfromEnum :: DecidedStrictness -> Int toEnum :: Int -> DecidedStrictness $ctoEnum :: Int -> DecidedStrictness pred :: DecidedStrictness -> DecidedStrictness $cpred :: DecidedStrictness -> DecidedStrictness succ :: DecidedStrictness -> DecidedStrictness $csucc :: DecidedStrictness -> DecidedStrictness Enum
, DecidedStrictness DecidedStrictness -> DecidedStrictness -> Bounded DecidedStrictness forall a. a -> a -> Bounded a maxBound :: DecidedStrictness $cmaxBound :: DecidedStrictness minBound :: DecidedStrictness $cminBound :: DecidedStrictness Bounded , Ord DecidedStrictness Ord DecidedStrictness -> ((DecidedStrictness, DecidedStrictness) -> [DecidedStrictness]) -> ((DecidedStrictness, DecidedStrictness) -> DecidedStrictness -> Int) -> ((DecidedStrictness, DecidedStrictness) -> DecidedStrictness -> Int) -> ((DecidedStrictness, DecidedStrictness) -> DecidedStrictness -> Bool) -> ((DecidedStrictness, DecidedStrictness) -> Int) -> ((DecidedStrictness, DecidedStrictness) -> Int) -> Ix DecidedStrictness (DecidedStrictness, DecidedStrictness) -> Int (DecidedStrictness, DecidedStrictness) -> [DecidedStrictness] (DecidedStrictness, DecidedStrictness) -> DecidedStrictness -> Bool (DecidedStrictness, DecidedStrictness) -> DecidedStrictness -> Int forall a. Ord a -> ((a, a) -> [a]) -> ((a, a) -> a -> Int) -> ((a, a) -> a -> Int) -> ((a, a) -> a -> Bool) -> ((a, a) -> Int) -> ((a, a) -> Int) -> Ix a unsafeRangeSize :: (DecidedStrictness, DecidedStrictness) -> Int $cunsafeRangeSize :: (DecidedStrictness, DecidedStrictness) -> Int rangeSize :: (DecidedStrictness, DecidedStrictness) -> Int $crangeSize :: (DecidedStrictness, DecidedStrictness) -> Int inRange :: (DecidedStrictness, DecidedStrictness) -> DecidedStrictness -> Bool $cinRange :: (DecidedStrictness, DecidedStrictness) -> DecidedStrictness -> Bool unsafeIndex :: (DecidedStrictness, DecidedStrictness) -> DecidedStrictness -> Int $cunsafeIndex :: (DecidedStrictness, DecidedStrictness) -> DecidedStrictness -> Int index :: (DecidedStrictness, DecidedStrictness) -> DecidedStrictness -> Int $cindex :: (DecidedStrictness, DecidedStrictness) -> DecidedStrictness -> Int range :: (DecidedStrictness, DecidedStrictness) -> [DecidedStrictness] $crange :: (DecidedStrictness, DecidedStrictness) -> [DecidedStrictness] Ix
, (forall x. DecidedStrictness -> Rep DecidedStrictness x) -> (forall x. Rep DecidedStrictness x -> DecidedStrictness) -> Generic DecidedStrictness forall x. Rep DecidedStrictness x -> DecidedStrictness forall x. DecidedStrictness -> Rep DecidedStrictness x forall a. (forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a $cto :: forall x. Rep DecidedStrictness x -> DecidedStrictness $cfrom :: forall x. DecidedStrictness -> Rep DecidedStrictness x Generic )
selName :: t s (f :: k -> Type) (a :: k) -> [Char]
selSourceUnpackedness :: t s (f :: k -> Type) (a :: k) -> SourceUnpackedness
selSourceStrictness :: t s (f :: k -> Type) (a :: k) -> SourceStrictness
selDecidedStrictness :: t s (f :: k -> Type) (a :: k) -> DecidedStrictness
instance (SingI mn, SingI su, SingI ss, SingI ds) => Selector ('MetaSel mn su ss ds) where selName :: forall k (t :: Meta -> (k -> *) -> k -> *) (f :: k -> *) (a :: k). t ('MetaSel mn su ss ds) f a -> String selName t ('MetaSel mn su ss ds) f a _ = String -> Maybe String -> String forall a. a -> Maybe a -> a fromMaybe String "" (Sing mn -> DemoteRep (Maybe Symbol) forall k (a :: k). SingKind k => Sing a -> DemoteRep k fromSing (Sing mn forall k (a :: k). SingI a => Sing a sing :: Sing mn)) selSourceUnpackedness :: forall k (t :: Meta -> (k -> *) -> k -> *) (f :: k -> *) (a :: k). t ('MetaSel mn su ss ds) f a -> SourceUnpackedness selSourceUnpackedness t ('MetaSel mn su ss ds) f a _ = Sing su -> DemoteRep SourceUnpackedness forall k (a :: k). SingKind k => Sing a -> DemoteRep k fromSing (Sing su forall k (a :: k). SingI a => Sing a sing :: Sing su) selSourceStrictness :: forall k (t :: Meta -> (k -> *) -> k -> *) (f :: k -> *) (a :: k). t ('MetaSel mn su ss ds) f a -> SourceStrictness selSourceStrictness t ('MetaSel mn su ss ds) f a _ = Sing ss -> DemoteRep SourceStrictness forall k (a :: k). SingKind k => Sing a -> DemoteRep k fromSing (Sing ss forall k (a :: k). SingI a => Sing a sing :: Sing ss) selDecidedStrictness :: forall k (t :: Meta -> (k -> *) -> k -> *) (f :: k -> *) (a :: k). t ('MetaSel mn su ss ds) f a -> DecidedStrictness selDecidedStrictness t ('MetaSel mn su ss ds) f a _ = Sing ds -> DemoteRep DecidedStrictness forall k (a :: k). SingKind k => Sing a -> DemoteRep k fromSing (Sing ds forall k (a :: k). SingI a => Sing a sing :: Sing ds)
class Generic1 (f :: k -> Type) where
data Meta = MetaData Symbol Symbol Symbol Bool | MetaCons Symbol FixityI Bool | MetaSel (Maybe Symbol) SourceUnpackedness SourceStrictness DecidedStrictness
deriving instance Generic (NonEmpty a)
deriving instance Generic (Maybe a)
deriving instance Generic (Either a b)
deriving instance Generic Bool
deriving instance Generic Ordering
deriving instance Generic (Proxy t)
deriving instance Generic ()
deriving instance Generic (Solo a)
deriving instance Generic ((,) a b)
deriving instance Generic ((,,) a b c)
deriving instance Generic ((,,,) a b c d)
deriving instance Generic ((,,,,) a b c d e)
deriving instance Generic ((,,,,,) a b c d e f)
deriving instance Generic ((,,,,,,) a b c d e f g)
deriving instance Generic ((,,,,,,,) a b c d e f g h)
deriving instance Generic ((,,,,,,,,) a b c d e f g h i)
deriving instance Generic ((,,,,,,,,,) a b c d e f g h i j)
deriving instance Generic ((,,,,,,,,,,) a b c d e f g h i j k)
deriving instance Generic ((,,,,,,,,,,,) a b c d e f g h i j k l)
deriving instance Generic ((,,,,,,,,,,,,) a b c d e f g h i j k l m)
deriving instance Generic ((,,,,,,,,,,,,,) a b c d e f g h i j k l m n)
deriving instance Generic ((,,,,,,,,,,,,,,) a b c d e f g h i j k l m n o)
deriving instance Generic (Down a)
deriving instance Generic SrcLoc
deriving instance Generic GeneralCategory
deriving instance Generic Fingerprint
deriving instance Generic1 []
deriving instance Generic1 NonEmpty
deriving instance Generic1 Maybe
deriving instance Generic1 (Either a)
deriving instance Generic1 Proxy
deriving instance Generic1 Solo
deriving instance Generic1 ((,) a)
deriving instance Generic1 ((,,) a b)
deriving instance Generic1 ((,,,) a b c)
deriving instance Generic1 ((,,,,) a b c d)
deriving instance Generic1 ((,,,,,) a b c d e)
deriving instance Generic1 ((,,,,,,) a b c d e f)
deriving instance Generic1 ((,,,,,,,) a b c d e f g)
deriving instance Generic1 ((,,,,,,,,) a b c d e f g h)
deriving instance Generic1 ((,,,,,,,,,) a b c d e f g h i)
deriving instance Generic1 ((,,,,,,,,,,) a b c d e f g h i j)
deriving instance Generic1 ((,,,,,,,,,,,) a b c d e f g h i j k)
deriving instance Generic1 ((,,,,,,,,,,,,) a b c d e f g h i j k l)
deriving instance Generic1 ((,,,,,,,,,,,,,) a b c d e f g h i j k l m)
deriving instance Generic1 ((,,,,,,,,,,,,,,) a b c d e f g h i j k l m n)
deriving instance Generic1 Down
fromSing :: Sing (a :: k) -> DemoteRep k
data instance Sing (s :: Symbol) where SSym :: KnownSymbol s => Sing s
instance KnownSymbol a => SingI a where sing :: Sing a sing = Sing a forall (a :: Symbol). KnownSymbol a => Sing a SSym
instance SingKind Symbol where type DemoteRep Symbol = String fromSing :: forall (a :: Symbol). Sing a -> DemoteRep Symbol fromSing (Sing a R:SingSymbols a SSym :: Sing s) = Proxy a -> String forall (n :: Symbol) (proxy :: Symbol -> *). KnownSymbol n => proxy n -> String symbolVal (Proxy a forall {k} (t :: k). Proxy t Proxy :: Proxy s)
data instance Sing (a :: Bool) where STrue :: Sing 'True SFalse :: Sing 'False
instance SingI 'True where sing :: Sing 'True sing = Sing 'True STrue
instance SingI 'False where sing :: Sing 'False sing = Sing 'False SFalse
instance SingKind Bool where type DemoteRep Bool = Bool fromSing :: forall (a :: Bool). Sing a -> DemoteRep Bool fromSing Sing a R:SingBoola a STrue = Bool DemoteRep Bool True fromSing Sing a R:SingBoola a SFalse = Bool DemoteRep Bool False
data instance Sing (b :: Maybe a) where SNothing :: Sing 'Nothing SJust :: Sing a -> Sing ('Just a)
instance SingI 'Nothing where sing :: Sing 'Nothing sing = Sing 'Nothing forall a. Sing 'Nothing SNothing
instance SingI a => SingI ('Just a) where sing :: Sing ('Just a) sing = Sing a -> Sing ('Just a) forall {k} (a :: k). Sing a -> Sing ('Just a) SJust Sing a forall k (a :: k). SingI a => Sing a sing
instance SingKind a => SingKind (Maybe a) where type DemoteRep (Maybe a) = Maybe (DemoteRep a) fromSing :: forall (a :: Maybe a). Sing a -> DemoteRep (Maybe a) fromSing Sing a R:SingMaybeb a a SNothing = DemoteRep (Maybe a) forall a. Maybe a Nothing fromSing (SJust Sing a a) = DemoteRep a -> Maybe (DemoteRep a) forall a. a -> Maybe a Just (Sing a -> DemoteRep a forall k (a :: k). SingKind k => Sing a -> DemoteRep k fromSing Sing a a)
data instance Sing (a :: FixityI) where SPrefix :: Sing 'PrefixI SInfix :: Sing a -> Integer -> Sing ('InfixI a n)
instance SingI 'PrefixI where sing :: Sing 'PrefixI sing = Sing 'PrefixI SPrefix
instance (SingI a, KnownNat n) => SingI ('InfixI a n) where sing :: Sing ('InfixI a n) sing = Sing a -> Integer -> Sing ('InfixI a n) forall (a :: Associativity) (n :: Nat). Sing a -> Integer -> Sing ('InfixI a n) SInfix (Sing a forall k (a :: k). SingI a => Sing a sing :: Sing a) (Proxy n -> Integer forall (n :: Nat) (proxy :: Nat -> *). KnownNat n => proxy n -> Integer natVal (Proxy n forall {k} (t :: k). Proxy t Proxy :: Proxy n))
instance SingKind FixityI where type DemoteRep FixityI = Fixity fromSing :: forall (a :: FixityI). Sing a -> DemoteRep FixityI fromSing Sing a R:SingFixityIa a SPrefix = Fixity DemoteRep FixityI Prefix fromSing (SInfix Sing a a Integer n) = Associativity -> Int -> Fixity Infix (Sing a -> DemoteRep Associativity forall k (a :: k). SingKind k => Sing a -> DemoteRep k fromSing Sing a a) (Integer -> Int integerToInt Integer n)
data instance Sing (a :: Associativity) where SLeftAssociative :: Sing 'LeftAssociative SRightAssociative :: Sing 'RightAssociative SNotAssociative :: Sing 'NotAssociative
instance SingI 'LeftAssociative where sing :: Sing 'LeftAssociative sing = Sing 'LeftAssociative SLeftAssociative
instance SingI 'RightAssociative where sing :: Sing 'RightAssociative sing = Sing 'RightAssociative SRightAssociative
instance SingI 'NotAssociative where sing :: Sing 'NotAssociative sing = Sing 'NotAssociative SNotAssociative
instance SingKind Associativity where type DemoteRep Associativity = Associativity fromSing :: forall (a :: Associativity). Sing a -> DemoteRep Associativity fromSing Sing a R:SingAssociativitya a SLeftAssociative = Associativity DemoteRep Associativity LeftAssociative fromSing Sing a R:SingAssociativitya a SRightAssociative = Associativity DemoteRep Associativity RightAssociative fromSing Sing a R:SingAssociativitya a SNotAssociative = Associativity DemoteRep Associativity NotAssociative
data instance Sing (a :: SourceUnpackedness) where SNoSourceUnpackedness :: Sing 'NoSourceUnpackedness SSourceNoUnpack :: Sing 'SourceNoUnpack SSourceUnpack :: Sing 'SourceUnpack
instance SingI 'NoSourceUnpackedness where sing :: Sing 'NoSourceUnpackedness sing = Sing 'NoSourceUnpackedness SNoSourceUnpackedness
instance SingI 'SourceNoUnpack where sing :: Sing 'SourceNoUnpack sing = Sing 'SourceNoUnpack SSourceNoUnpack
instance SingI 'SourceUnpack where sing :: Sing 'SourceUnpack sing = Sing 'SourceUnpack SSourceUnpack
instance SingKind SourceUnpackedness where type DemoteRep SourceUnpackedness = SourceUnpackedness fromSing :: forall (a :: SourceUnpackedness). Sing a -> DemoteRep SourceUnpackedness fromSing Sing a R:SingSourceUnpackednessa a SNoSourceUnpackedness = SourceUnpackedness DemoteRep SourceUnpackedness NoSourceUnpackedness fromSing Sing a R:SingSourceUnpackednessa a SSourceNoUnpack = SourceUnpackedness DemoteRep SourceUnpackedness SourceNoUnpack fromSing Sing a R:SingSourceUnpackednessa a SSourceUnpack = SourceUnpackedness DemoteRep SourceUnpackedness SourceUnpack
data instance Sing (a :: SourceStrictness) where SNoSourceStrictness :: Sing 'NoSourceStrictness SSourceLazy :: Sing 'SourceLazy SSourceStrict :: Sing 'SourceStrict
instance SingI 'NoSourceStrictness where sing :: Sing 'NoSourceStrictness sing = Sing 'NoSourceStrictness SNoSourceStrictness
instance SingI 'SourceLazy where sing :: Sing 'SourceLazy sing = Sing 'SourceLazy SSourceLazy
instance SingI 'SourceStrict where sing :: Sing 'SourceStrict sing = Sing 'SourceStrict SSourceStrict
instance SingKind SourceStrictness where type DemoteRep SourceStrictness = SourceStrictness fromSing :: forall (a :: SourceStrictness). Sing a -> DemoteRep SourceStrictness fromSing Sing a R:SingSourceStrictnessa a SNoSourceStrictness = SourceStrictness DemoteRep SourceStrictness NoSourceStrictness fromSing Sing a R:SingSourceStrictnessa a SSourceLazy = SourceStrictness DemoteRep SourceStrictness SourceLazy fromSing Sing a R:SingSourceStrictnessa a SSourceStrict = SourceStrictness DemoteRep SourceStrictness SourceStrict
data instance Sing (a :: DecidedStrictness) where SDecidedLazy :: Sing 'DecidedLazy SDecidedStrict :: Sing 'DecidedStrict SDecidedUnpack :: Sing 'DecidedUnpack
instance SingI 'DecidedLazy where sing :: Sing 'DecidedLazy sing = Sing 'DecidedLazy SDecidedLazy
instance SingI 'DecidedStrict where sing :: Sing 'DecidedStrict sing = Sing 'DecidedStrict SDecidedStrict
instance SingI 'DecidedUnpack where sing :: Sing 'DecidedUnpack sing = Sing 'DecidedUnpack SDecidedUnpack
instance SingKind DecidedStrictness where type DemoteRep DecidedStrictness = DecidedStrictness fromSing :: forall (a :: DecidedStrictness). Sing a -> DemoteRep DecidedStrictness fromSing Sing a R:SingDecidedStrictnessa a SDecidedLazy = DecidedStrictness DemoteRep DecidedStrictness DecidedLazy fromSing Sing a R:SingDecidedStrictnessa a SDecidedStrict = DecidedStrictness DemoteRep DecidedStrictness DecidedStrict fromSing Sing a R:SingDecidedStrictnessa a SDecidedUnpack = DecidedStrictness DemoteRep DecidedStrictness DecidedUnpack