bytepatch-0.4.1: Patch byte-representable data in a bytestream
Safe HaskellSafe-Inferred
LanguageGHC2021

StreamPatch.Patch.Compare

Synopsis

Documentation

data EqualityCheck Source #

Constructors

Exact 
PrefixOf 

Instances

Instances details
Data EqualityCheck Source # 
Instance details

Defined in StreamPatch.Patch.Compare

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> EqualityCheck -> c EqualityCheck #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c EqualityCheck #

toConstr :: EqualityCheck -> Constr #

dataTypeOf :: EqualityCheck -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c EqualityCheck) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c EqualityCheck) #

gmapT :: (forall b. Data b => b -> b) -> EqualityCheck -> EqualityCheck #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> EqualityCheck -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> EqualityCheck -> r #

gmapQ :: (forall d. Data d => d -> u) -> EqualityCheck -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> EqualityCheck -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> EqualityCheck -> m EqualityCheck #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> EqualityCheck -> m EqualityCheck #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> EqualityCheck -> m EqualityCheck #

Generic EqualityCheck Source # 
Instance details

Defined in StreamPatch.Patch.Compare

Associated Types

type Rep EqualityCheck :: Type -> Type #

Show EqualityCheck Source # 
Instance details

Defined in StreamPatch.Patch.Compare

Eq EqualityCheck Source # 
Instance details

Defined in StreamPatch.Patch.Compare

SingKind EqualityCheck Source # 
Instance details

Defined in StreamPatch.Patch.Compare

Associated Types

type Demote EqualityCheck = (r :: Type) #

SDecide EqualityCheck Source # 
Instance details

Defined in StreamPatch.Patch.Compare

Methods

(%~) :: forall (a :: EqualityCheck) (b :: EqualityCheck). Sing a -> Sing b -> Decision (a :~: b) #

PEq EqualityCheck Source # 
Instance details

Defined in StreamPatch.Patch.Compare

Associated Types

type arg == arg1 :: Bool #

type arg /= arg1 :: Bool #

SEq EqualityCheck Source # 
Instance details

Defined in StreamPatch.Patch.Compare

Methods

(%==) :: forall (t1 :: EqualityCheck) (t2 :: EqualityCheck). Sing t1 -> Sing t2 -> Sing (Apply (Apply (==@#@$) t1) t2) #

(%/=) :: forall (t1 :: EqualityCheck) (t2 :: EqualityCheck). Sing t1 -> Sing t2 -> Sing (Apply (Apply (/=@#@$) t1) t2) #

PShow EqualityCheck Source # 
Instance details

Defined in StreamPatch.Patch.Compare

Associated Types

type ShowsPrec arg arg1 arg2 :: Symbol #

type Show_ arg :: Symbol #

type ShowList arg arg1 :: Symbol #

SShow EqualityCheck Source # 
Instance details

Defined in StreamPatch.Patch.Compare

Methods

sShowsPrec :: forall (t1 :: Natural) (t2 :: EqualityCheck) (t3 :: Symbol). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply ShowsPrecSym0 t1) t2) t3) #

sShow_ :: forall (t :: EqualityCheck). Sing t -> Sing (Apply Show_Sym0 t) #

sShowList :: forall (t1 :: [EqualityCheck]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply ShowListSym0 t1) t2) #

TestCoercion SEqualityCheck Source # 
Instance details

Defined in StreamPatch.Patch.Compare

Methods

testCoercion :: forall (a :: k) (b :: k). SEqualityCheck a -> SEqualityCheck b -> Maybe (Coercion a b) #

TestEquality SEqualityCheck Source # 
Instance details

Defined in StreamPatch.Patch.Compare

Methods

testEquality :: forall (a :: k) (b :: k). SEqualityCheck a -> SEqualityCheck b -> Maybe (a :~: b) #

SingI 'Exact Source # 
Instance details

Defined in StreamPatch.Patch.Compare

Methods

sing :: Sing 'Exact #

SingI 'PrefixOf Source # 
Instance details

Defined in StreamPatch.Patch.Compare

Methods

sing :: Sing 'PrefixOf #

SingI1 'ViaEq Source # 
Instance details

Defined in StreamPatch.Patch.Compare

Methods

liftSing :: forall (x :: k1). Sing x -> Sing ('ViaEq x) #

SingI ViaEqSym0 Source # 
Instance details

Defined in StreamPatch.Patch.Compare

Methods

sing :: Sing ViaEqSym0 #

SuppressUnusedWarnings ViaEqSym0 Source # 
Instance details

Defined in StreamPatch.Patch.Compare

SuppressUnusedWarnings TFHelper_6989586621679160119Sym0 Source # 
Instance details

Defined in StreamPatch.Patch.Compare

SuppressUnusedWarnings ShowsPrec_6989586621679159583Sym0 Source # 
Instance details

Defined in StreamPatch.Patch.Compare

SuppressUnusedWarnings (ShowsPrec_6989586621679159583Sym1 a6989586621679159593 :: TyFun EqualityCheck (Symbol ~> Symbol) -> Type) Source # 
Instance details

Defined in StreamPatch.Patch.Compare

SuppressUnusedWarnings (TFHelper_6989586621679160119Sym1 a6989586621679160124 :: TyFun EqualityCheck Bool -> Type) Source # 
Instance details

Defined in StreamPatch.Patch.Compare

type Rep EqualityCheck Source # 
Instance details

Defined in StreamPatch.Patch.Compare

type Rep EqualityCheck = D1 ('MetaData "EqualityCheck" "StreamPatch.Patch.Compare" "bytepatch-0.4.1-inplace" 'False) (C1 ('MetaCons "Exact" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PrefixOf" 'PrefixI 'False) (U1 :: Type -> Type))
type Demote EqualityCheck Source # 
Instance details

Defined in StreamPatch.Patch.Compare

type Sing Source # 
Instance details

Defined in StreamPatch.Patch.Compare

type Show_ (arg :: EqualityCheck) Source # 
Instance details

Defined in StreamPatch.Patch.Compare

type Show_ (arg :: EqualityCheck) = Apply (Show__6989586621680009330Sym0 :: TyFun EqualityCheck Symbol -> Type) arg
type (arg :: EqualityCheck) /= (arg1 :: EqualityCheck) Source # 
Instance details

Defined in StreamPatch.Patch.Compare

type (arg :: EqualityCheck) /= (arg1 :: EqualityCheck) = Apply (Apply (TFHelper_6989586621679137069Sym0 :: TyFun EqualityCheck (EqualityCheck ~> Bool) -> Type) arg) arg1
type (a1 :: EqualityCheck) == (a2 :: EqualityCheck) Source # 
Instance details

Defined in StreamPatch.Patch.Compare

type ShowList (arg :: [EqualityCheck]) arg1 Source # 
Instance details

Defined in StreamPatch.Patch.Compare

type ShowList (arg :: [EqualityCheck]) arg1 = Apply (Apply (ShowList_6989586621680009344Sym0 :: TyFun [EqualityCheck] (Symbol ~> Symbol) -> Type) arg) arg1
type Apply ViaEqSym0 (a6989586621679180915 :: EqualityCheck) Source # 
Instance details

Defined in StreamPatch.Patch.Compare

type Apply ViaEqSym0 (a6989586621679180915 :: EqualityCheck) = 'ViaEq a6989586621679180915
type ShowsPrec a1 (a2 :: EqualityCheck) a3 Source # 
Instance details

Defined in StreamPatch.Patch.Compare

type Apply (TFHelper_6989586621679160119Sym1 a6989586621679160124 :: TyFun EqualityCheck Bool -> Type) (a6989586621679160125 :: EqualityCheck) Source # 
Instance details

Defined in StreamPatch.Patch.Compare

type Apply (TFHelper_6989586621679160119Sym1 a6989586621679160124 :: TyFun EqualityCheck Bool -> Type) (a6989586621679160125 :: EqualityCheck) = TFHelper_6989586621679160119 a6989586621679160124 a6989586621679160125
type Apply TFHelper_6989586621679160119Sym0 (a6989586621679160124 :: EqualityCheck) Source # 
Instance details

Defined in StreamPatch.Patch.Compare

type Apply TFHelper_6989586621679160119Sym0 (a6989586621679160124 :: EqualityCheck) = TFHelper_6989586621679160119Sym1 a6989586621679160124
type Apply ShowsPrec_6989586621679159583Sym0 (a6989586621679159593 :: Natural) Source # 
Instance details

Defined in StreamPatch.Patch.Compare

type Apply ShowsPrec_6989586621679159583Sym0 (a6989586621679159593 :: Natural) = ShowsPrec_6989586621679159583Sym1 a6989586621679159593
type Apply (ShowsPrec_6989586621679159583Sym1 a6989586621679159593 :: TyFun EqualityCheck (Symbol ~> Symbol) -> Type) (a6989586621679159594 :: EqualityCheck) Source # 
Instance details

Defined in StreamPatch.Patch.Compare

type Apply (ShowsPrec_6989586621679159583Sym1 a6989586621679159593 :: TyFun EqualityCheck (Symbol ~> Symbol) -> Type) (a6989586621679159594 :: EqualityCheck) = ShowsPrec_6989586621679159583Sym2 a6989586621679159593 a6989586621679159594

type family ExactSym0 :: EqualityCheck where ... Source #

Equations

ExactSym0 = Exact 

type family PrefixOfSym0 :: EqualityCheck where ... Source #

Equations

PrefixOfSym0 = PrefixOf 

type family ShowsPrec_6989586621679159583 (a :: Natural) (a :: EqualityCheck) (a :: Symbol) :: Symbol where ... Source #

Equations

ShowsPrec_6989586621679159583 _ Exact a_6989586621679159585 = Apply (Apply ShowStringSym0 (FromString "Exact")) a_6989586621679159585 
ShowsPrec_6989586621679159583 _ PrefixOf a_6989586621679159587 = Apply (Apply ShowStringSym0 (FromString "PrefixOf")) a_6989586621679159587 

type family ShowsPrec_6989586621679159583Sym3 (a6989586621679159593 :: Natural) (a6989586621679159594 :: EqualityCheck) (a6989586621679159595 :: Symbol) :: Symbol where ... Source #

Equations

ShowsPrec_6989586621679159583Sym3 a6989586621679159593 a6989586621679159594 a6989586621679159595 = ShowsPrec_6989586621679159583 a6989586621679159593 a6989586621679159594 a6989586621679159595 

data ShowsPrec_6989586621679159583Sym2 (a6989586621679159593 :: Natural) (a6989586621679159594 :: EqualityCheck) :: (~>) Symbol Symbol where Source #

Constructors

ShowsPrec_6989586621679159583Sym2KindInference :: SameKind (Apply (ShowsPrec_6989586621679159583Sym2 a6989586621679159593 a6989586621679159594) arg) (ShowsPrec_6989586621679159583Sym3 a6989586621679159593 a6989586621679159594 arg) => ShowsPrec_6989586621679159583Sym2 a6989586621679159593 a6989586621679159594 a6989586621679159595 

Instances

Instances details
SuppressUnusedWarnings (ShowsPrec_6989586621679159583Sym2 a6989586621679159593 a6989586621679159594 :: TyFun Symbol Symbol -> Type) Source # 
Instance details

Defined in StreamPatch.Patch.Compare

type Apply (ShowsPrec_6989586621679159583Sym2 a6989586621679159593 a6989586621679159594 :: TyFun Symbol Symbol -> Type) (a6989586621679159595 :: Symbol) Source # 
Instance details

Defined in StreamPatch.Patch.Compare

type Apply (ShowsPrec_6989586621679159583Sym2 a6989586621679159593 a6989586621679159594 :: TyFun Symbol Symbol -> Type) (a6989586621679159595 :: Symbol) = ShowsPrec_6989586621679159583 a6989586621679159593 a6989586621679159594 a6989586621679159595

data ShowsPrec_6989586621679159583Sym1 (a6989586621679159593 :: Natural) :: (~>) EqualityCheck ((~>) Symbol Symbol) where Source #

Constructors

ShowsPrec_6989586621679159583Sym1KindInference :: SameKind (Apply (ShowsPrec_6989586621679159583Sym1 a6989586621679159593) arg) (ShowsPrec_6989586621679159583Sym2 a6989586621679159593 arg) => ShowsPrec_6989586621679159583Sym1 a6989586621679159593 a6989586621679159594 

Instances

Instances details
SuppressUnusedWarnings (ShowsPrec_6989586621679159583Sym1 a6989586621679159593 :: TyFun EqualityCheck (Symbol ~> Symbol) -> Type) Source # 
Instance details

Defined in StreamPatch.Patch.Compare

type Apply (ShowsPrec_6989586621679159583Sym1 a6989586621679159593 :: TyFun EqualityCheck (Symbol ~> Symbol) -> Type) (a6989586621679159594 :: EqualityCheck) Source # 
Instance details

Defined in StreamPatch.Patch.Compare

type Apply (ShowsPrec_6989586621679159583Sym1 a6989586621679159593 :: TyFun EqualityCheck (Symbol ~> Symbol) -> Type) (a6989586621679159594 :: EqualityCheck) = ShowsPrec_6989586621679159583Sym2 a6989586621679159593 a6989586621679159594

type family TFHelper_6989586621679160119Sym2 (a6989586621679160124 :: EqualityCheck) (a6989586621679160125 :: EqualityCheck) :: Bool where ... Source #

Equations

TFHelper_6989586621679160119Sym2 a6989586621679160124 a6989586621679160125 = TFHelper_6989586621679160119 a6989586621679160124 a6989586621679160125 

data TFHelper_6989586621679160119Sym1 (a6989586621679160124 :: EqualityCheck) :: (~>) EqualityCheck Bool where Source #

Constructors

TFHelper_6989586621679160119Sym1KindInference :: SameKind (Apply (TFHelper_6989586621679160119Sym1 a6989586621679160124) arg) (TFHelper_6989586621679160119Sym2 a6989586621679160124 arg) => TFHelper_6989586621679160119Sym1 a6989586621679160124 a6989586621679160125 

Instances

Instances details
SuppressUnusedWarnings (TFHelper_6989586621679160119Sym1 a6989586621679160124 :: TyFun EqualityCheck Bool -> Type) Source # 
Instance details

Defined in StreamPatch.Patch.Compare

type Apply (TFHelper_6989586621679160119Sym1 a6989586621679160124 :: TyFun EqualityCheck Bool -> Type) (a6989586621679160125 :: EqualityCheck) Source # 
Instance details

Defined in StreamPatch.Patch.Compare

type Apply (TFHelper_6989586621679160119Sym1 a6989586621679160124 :: TyFun EqualityCheck Bool -> Type) (a6989586621679160125 :: EqualityCheck) = TFHelper_6989586621679160119 a6989586621679160124 a6989586621679160125

data SEqualityCheck :: EqualityCheck -> Type where Source #

Instances

Instances details
TestCoercion SEqualityCheck Source # 
Instance details

Defined in StreamPatch.Patch.Compare

Methods

testCoercion :: forall (a :: k) (b :: k). SEqualityCheck a -> SEqualityCheck b -> Maybe (Coercion a b) #

TestEquality SEqualityCheck Source # 
Instance details

Defined in StreamPatch.Patch.Compare

Methods

testEquality :: forall (a :: k) (b :: k). SEqualityCheck a -> SEqualityCheck b -> Maybe (a :~: b) #

Show (SEqualityCheck z) Source # 
Instance details

Defined in StreamPatch.Patch.Compare

data HashFunc Source #

Constructors

B3 
SHA256 
MD5 

Instances

Instances details
Data HashFunc Source # 
Instance details

Defined in StreamPatch.Patch.Compare

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HashFunc -> c HashFunc #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c HashFunc #

toConstr :: HashFunc -> Constr #

dataTypeOf :: HashFunc -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c HashFunc) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c HashFunc) #

gmapT :: (forall b. Data b => b -> b) -> HashFunc -> HashFunc #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HashFunc -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HashFunc -> r #

gmapQ :: (forall d. Data d => d -> u) -> HashFunc -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HashFunc -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HashFunc -> m HashFunc #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HashFunc -> m HashFunc #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HashFunc -> m HashFunc #

Generic HashFunc Source # 
Instance details

Defined in StreamPatch.Patch.Compare

Associated Types

type Rep HashFunc :: Type -> Type #

Methods

from :: HashFunc -> Rep HashFunc x #

to :: Rep HashFunc x -> HashFunc #

Show HashFunc Source # 
Instance details

Defined in StreamPatch.Patch.Compare

Eq HashFunc Source # 
Instance details

Defined in StreamPatch.Patch.Compare

SingKind HashFunc Source # 
Instance details

Defined in StreamPatch.Patch.Compare

Associated Types

type Demote HashFunc = (r :: Type) #

SDecide HashFunc Source # 
Instance details

Defined in StreamPatch.Patch.Compare

Methods

(%~) :: forall (a :: HashFunc) (b :: HashFunc). Sing a -> Sing b -> Decision (a :~: b) #

PEq HashFunc Source # 
Instance details

Defined in StreamPatch.Patch.Compare

Associated Types

type arg == arg1 :: Bool #

type arg /= arg1 :: Bool #

SEq HashFunc Source # 
Instance details

Defined in StreamPatch.Patch.Compare

Methods

(%==) :: forall (t1 :: HashFunc) (t2 :: HashFunc). Sing t1 -> Sing t2 -> Sing (Apply (Apply (==@#@$) t1) t2) #

(%/=) :: forall (t1 :: HashFunc) (t2 :: HashFunc). Sing t1 -> Sing t2 -> Sing (Apply (Apply (/=@#@$) t1) t2) #

PShow HashFunc Source # 
Instance details

Defined in StreamPatch.Patch.Compare

Associated Types

type ShowsPrec arg arg1 arg2 :: Symbol #

type Show_ arg :: Symbol #

type ShowList arg arg1 :: Symbol #

SShow HashFunc Source # 
Instance details

Defined in StreamPatch.Patch.Compare

Methods

sShowsPrec :: forall (t1 :: Natural) (t2 :: HashFunc) (t3 :: Symbol). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply ShowsPrecSym0 t1) t2) t3) #

sShow_ :: forall (t :: HashFunc). Sing t -> Sing (Apply Show_Sym0 t) #

sShowList :: forall (t1 :: [HashFunc]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply ShowListSym0 t1) t2) #

TestCoercion SHashFunc Source # 
Instance details

Defined in StreamPatch.Patch.Compare

Methods

testCoercion :: forall (a :: k) (b :: k). SHashFunc a -> SHashFunc b -> Maybe (Coercion a b) #

TestEquality SHashFunc Source # 
Instance details

Defined in StreamPatch.Patch.Compare

Methods

testEquality :: forall (a :: k) (b :: k). SHashFunc a -> SHashFunc b -> Maybe (a :~: b) #

SingI 'B3 Source # 
Instance details

Defined in StreamPatch.Patch.Compare

Methods

sing :: Sing 'B3 #

SingI 'MD5 Source # 
Instance details

Defined in StreamPatch.Patch.Compare

Methods

sing :: Sing 'MD5 #

SingI 'SHA256 Source # 
Instance details

Defined in StreamPatch.Patch.Compare

Methods

sing :: Sing 'SHA256 #

SingI1 'ViaDigest Source # 
Instance details

Defined in StreamPatch.Patch.Compare

Methods

liftSing :: forall (x :: k1). Sing x -> Sing ('ViaDigest x) #

SingI ViaDigestSym0 Source # 
Instance details

Defined in StreamPatch.Patch.Compare

SuppressUnusedWarnings ViaDigestSym0 Source # 
Instance details

Defined in StreamPatch.Patch.Compare

SuppressUnusedWarnings TFHelper_6989586621679178722Sym0 Source # 
Instance details

Defined in StreamPatch.Patch.Compare

SuppressUnusedWarnings ShowsPrec_6989586621679178702Sym0 Source # 
Instance details

Defined in StreamPatch.Patch.Compare

SuppressUnusedWarnings (ShowsPrec_6989586621679178702Sym1 a6989586621679178714 :: TyFun HashFunc (Symbol ~> Symbol) -> Type) Source # 
Instance details

Defined in StreamPatch.Patch.Compare

SuppressUnusedWarnings (TFHelper_6989586621679178722Sym1 a6989586621679178727 :: TyFun HashFunc Bool -> Type) Source # 
Instance details

Defined in StreamPatch.Patch.Compare

type Rep HashFunc Source # 
Instance details

Defined in StreamPatch.Patch.Compare

type Rep HashFunc = D1 ('MetaData "HashFunc" "StreamPatch.Patch.Compare" "bytepatch-0.4.1-inplace" 'False) (C1 ('MetaCons "B3" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "SHA256" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MD5" 'PrefixI 'False) (U1 :: Type -> Type)))
type Demote HashFunc Source # 
Instance details

Defined in StreamPatch.Patch.Compare

type Sing Source # 
Instance details

Defined in StreamPatch.Patch.Compare

type Show_ (arg :: HashFunc) Source # 
Instance details

Defined in StreamPatch.Patch.Compare

type Show_ (arg :: HashFunc) = Apply (Show__6989586621680009330Sym0 :: TyFun HashFunc Symbol -> Type) arg
type (arg :: HashFunc) /= (arg1 :: HashFunc) Source # 
Instance details

Defined in StreamPatch.Patch.Compare

type (arg :: HashFunc) /= (arg1 :: HashFunc) = Apply (Apply (TFHelper_6989586621679137069Sym0 :: TyFun HashFunc (HashFunc ~> Bool) -> Type) arg) arg1
type (a1 :: HashFunc) == (a2 :: HashFunc) Source # 
Instance details

Defined in StreamPatch.Patch.Compare

type ShowList (arg :: [HashFunc]) arg1 Source # 
Instance details

Defined in StreamPatch.Patch.Compare

type ShowList (arg :: [HashFunc]) arg1 = Apply (Apply (ShowList_6989586621680009344Sym0 :: TyFun [HashFunc] (Symbol ~> Symbol) -> Type) arg) arg1
type Apply ViaDigestSym0 (a6989586621679180918 :: HashFunc) Source # 
Instance details

Defined in StreamPatch.Patch.Compare

type Apply ViaDigestSym0 (a6989586621679180918 :: HashFunc) = 'ViaDigest a6989586621679180918
type ShowsPrec a1 (a2 :: HashFunc) a3 Source # 
Instance details

Defined in StreamPatch.Patch.Compare

type Apply (TFHelper_6989586621679178722Sym1 a6989586621679178727 :: TyFun HashFunc Bool -> Type) (a6989586621679178728 :: HashFunc) Source # 
Instance details

Defined in StreamPatch.Patch.Compare

type Apply (TFHelper_6989586621679178722Sym1 a6989586621679178727 :: TyFun HashFunc Bool -> Type) (a6989586621679178728 :: HashFunc) = TFHelper_6989586621679178722 a6989586621679178727 a6989586621679178728
type Apply TFHelper_6989586621679178722Sym0 (a6989586621679178727 :: HashFunc) Source # 
Instance details

Defined in StreamPatch.Patch.Compare

type Apply TFHelper_6989586621679178722Sym0 (a6989586621679178727 :: HashFunc) = TFHelper_6989586621679178722Sym1 a6989586621679178727
type Apply ShowsPrec_6989586621679178702Sym0 (a6989586621679178714 :: Natural) Source # 
Instance details

Defined in StreamPatch.Patch.Compare

type Apply ShowsPrec_6989586621679178702Sym0 (a6989586621679178714 :: Natural) = ShowsPrec_6989586621679178702Sym1 a6989586621679178714
type Apply (ShowsPrec_6989586621679178702Sym1 a6989586621679178714 :: TyFun HashFunc (Symbol ~> Symbol) -> Type) (a6989586621679178715 :: HashFunc) Source # 
Instance details

Defined in StreamPatch.Patch.Compare

type Apply (ShowsPrec_6989586621679178702Sym1 a6989586621679178714 :: TyFun HashFunc (Symbol ~> Symbol) -> Type) (a6989586621679178715 :: HashFunc) = ShowsPrec_6989586621679178702Sym2 a6989586621679178714 a6989586621679178715

type family B3Sym0 :: HashFunc where ... Source #

Equations

B3Sym0 = B3 

type family SHA256Sym0 :: HashFunc where ... Source #

Equations

SHA256Sym0 = SHA256 

type family MD5Sym0 :: HashFunc where ... Source #

Equations

MD5Sym0 = MD5 

type family ShowsPrec_6989586621679178702 (a :: Natural) (a :: HashFunc) (a :: Symbol) :: Symbol where ... Source #

Equations

ShowsPrec_6989586621679178702 _ B3 a_6989586621679178704 = Apply (Apply ShowStringSym0 (FromString "B3")) a_6989586621679178704 
ShowsPrec_6989586621679178702 _ SHA256 a_6989586621679178706 = Apply (Apply ShowStringSym0 (FromString "SHA256")) a_6989586621679178706 
ShowsPrec_6989586621679178702 _ MD5 a_6989586621679178708 = Apply (Apply ShowStringSym0 (FromString "MD5")) a_6989586621679178708 

type family ShowsPrec_6989586621679178702Sym3 (a6989586621679178714 :: Natural) (a6989586621679178715 :: HashFunc) (a6989586621679178716 :: Symbol) :: Symbol where ... Source #

Equations

ShowsPrec_6989586621679178702Sym3 a6989586621679178714 a6989586621679178715 a6989586621679178716 = ShowsPrec_6989586621679178702 a6989586621679178714 a6989586621679178715 a6989586621679178716 

data ShowsPrec_6989586621679178702Sym2 (a6989586621679178714 :: Natural) (a6989586621679178715 :: HashFunc) :: (~>) Symbol Symbol where Source #

Constructors

ShowsPrec_6989586621679178702Sym2KindInference :: SameKind (Apply (ShowsPrec_6989586621679178702Sym2 a6989586621679178714 a6989586621679178715) arg) (ShowsPrec_6989586621679178702Sym3 a6989586621679178714 a6989586621679178715 arg) => ShowsPrec_6989586621679178702Sym2 a6989586621679178714 a6989586621679178715 a6989586621679178716 

Instances

Instances details
SuppressUnusedWarnings (ShowsPrec_6989586621679178702Sym2 a6989586621679178714 a6989586621679178715 :: TyFun Symbol Symbol -> Type) Source # 
Instance details

Defined in StreamPatch.Patch.Compare

type Apply (ShowsPrec_6989586621679178702Sym2 a6989586621679178714 a6989586621679178715 :: TyFun Symbol Symbol -> Type) (a6989586621679178716 :: Symbol) Source # 
Instance details

Defined in StreamPatch.Patch.Compare

type Apply (ShowsPrec_6989586621679178702Sym2 a6989586621679178714 a6989586621679178715 :: TyFun Symbol Symbol -> Type) (a6989586621679178716 :: Symbol) = ShowsPrec_6989586621679178702 a6989586621679178714 a6989586621679178715 a6989586621679178716

data ShowsPrec_6989586621679178702Sym1 (a6989586621679178714 :: Natural) :: (~>) HashFunc ((~>) Symbol Symbol) where Source #

Constructors

ShowsPrec_6989586621679178702Sym1KindInference :: SameKind (Apply (ShowsPrec_6989586621679178702Sym1 a6989586621679178714) arg) (ShowsPrec_6989586621679178702Sym2 a6989586621679178714 arg) => ShowsPrec_6989586621679178702Sym1 a6989586621679178714 a6989586621679178715 

Instances

Instances details
SuppressUnusedWarnings (ShowsPrec_6989586621679178702Sym1 a6989586621679178714 :: TyFun HashFunc (Symbol ~> Symbol) -> Type) Source # 
Instance details

Defined in StreamPatch.Patch.Compare

type Apply (ShowsPrec_6989586621679178702Sym1 a6989586621679178714 :: TyFun HashFunc (Symbol ~> Symbol) -> Type) (a6989586621679178715 :: HashFunc) Source # 
Instance details

Defined in StreamPatch.Patch.Compare

type Apply (ShowsPrec_6989586621679178702Sym1 a6989586621679178714 :: TyFun HashFunc (Symbol ~> Symbol) -> Type) (a6989586621679178715 :: HashFunc) = ShowsPrec_6989586621679178702Sym2 a6989586621679178714 a6989586621679178715

type family TFHelper_6989586621679178722Sym2 (a6989586621679178727 :: HashFunc) (a6989586621679178728 :: HashFunc) :: Bool where ... Source #

Equations

TFHelper_6989586621679178722Sym2 a6989586621679178727 a6989586621679178728 = TFHelper_6989586621679178722 a6989586621679178727 a6989586621679178728 

data TFHelper_6989586621679178722Sym1 (a6989586621679178727 :: HashFunc) :: (~>) HashFunc Bool where Source #

Constructors

TFHelper_6989586621679178722Sym1KindInference :: SameKind (Apply (TFHelper_6989586621679178722Sym1 a6989586621679178727) arg) (TFHelper_6989586621679178722Sym2 a6989586621679178727 arg) => TFHelper_6989586621679178722Sym1 a6989586621679178727 a6989586621679178728 

Instances

Instances details
SuppressUnusedWarnings (TFHelper_6989586621679178722Sym1 a6989586621679178727 :: TyFun HashFunc Bool -> Type) Source # 
Instance details

Defined in StreamPatch.Patch.Compare

type Apply (TFHelper_6989586621679178722Sym1 a6989586621679178727 :: TyFun HashFunc Bool -> Type) (a6989586621679178728 :: HashFunc) Source # 
Instance details

Defined in StreamPatch.Patch.Compare

type Apply (TFHelper_6989586621679178722Sym1 a6989586621679178727 :: TyFun HashFunc Bool -> Type) (a6989586621679178728 :: HashFunc) = TFHelper_6989586621679178722 a6989586621679178727 a6989586621679178728

data SHashFunc :: HashFunc -> Type where Source #

Constructors

SB3 :: SHashFunc (B3 :: HashFunc) 
SSHA256 :: SHashFunc (SHA256 :: HashFunc) 
SMD5 :: SHashFunc (MD5 :: HashFunc) 

Instances

Instances details
TestCoercion SHashFunc Source # 
Instance details

Defined in StreamPatch.Patch.Compare

Methods

testCoercion :: forall (a :: k) (b :: k). SHashFunc a -> SHashFunc b -> Maybe (Coercion a b) #

TestEquality SHashFunc Source # 
Instance details

Defined in StreamPatch.Patch.Compare

Methods

testEquality :: forall (a :: k) (b :: k). SHashFunc a -> SHashFunc b -> Maybe (a :~: b) #

Show (SHashFunc z) Source # 
Instance details

Defined in StreamPatch.Patch.Compare

data Via Source #

Instances

Instances details
Data Via Source # 
Instance details

Defined in StreamPatch.Patch.Compare

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Via -> c Via #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Via #

toConstr :: Via -> Constr #

dataTypeOf :: Via -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Via) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Via) #

gmapT :: (forall b. Data b => b -> b) -> Via -> Via #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Via -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Via -> r #

gmapQ :: (forall d. Data d => d -> u) -> Via -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Via -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Via -> m Via #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Via -> m Via #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Via -> m Via #

Generic Via Source # 
Instance details

Defined in StreamPatch.Patch.Compare

Associated Types

type Rep Via :: Type -> Type #

Methods

from :: Via -> Rep Via x #

to :: Rep Via x -> Via #

Show Via Source # 
Instance details

Defined in StreamPatch.Patch.Compare

Methods

showsPrec :: Int -> Via -> ShowS #

show :: Via -> String #

showList :: [Via] -> ShowS #

Eq Via Source # 
Instance details

Defined in StreamPatch.Patch.Compare

Methods

(==) :: Via -> Via -> Bool #

(/=) :: Via -> Via -> Bool #

SingKind Via Source # 
Instance details

Defined in StreamPatch.Patch.Compare

Associated Types

type Demote Via = (r :: Type) #

Methods

fromSing :: forall (a :: Via). Sing a -> Demote Via #

toSing :: Demote Via -> SomeSing Via #

(SDecide EqualityCheck, SDecide HashFunc) => SDecide Via Source # 
Instance details

Defined in StreamPatch.Patch.Compare

Methods

(%~) :: forall (a :: Via) (b :: Via). Sing a -> Sing b -> Decision (a :~: b) #

PEq Via Source # 
Instance details

Defined in StreamPatch.Patch.Compare

Associated Types

type arg == arg1 :: Bool #

type arg /= arg1 :: Bool #

(SEq EqualityCheck, SEq HashFunc) => SEq Via Source # 
Instance details

Defined in StreamPatch.Patch.Compare

Methods

(%==) :: forall (t1 :: Via) (t2 :: Via). Sing t1 -> Sing t2 -> Sing (Apply (Apply (==@#@$) t1) t2) #

(%/=) :: forall (t1 :: Via) (t2 :: Via). Sing t1 -> Sing t2 -> Sing (Apply (Apply (/=@#@$) t1) t2) #

PShow Via Source # 
Instance details

Defined in StreamPatch.Patch.Compare

Associated Types

type ShowsPrec arg arg1 arg2 :: Symbol #

type Show_ arg :: Symbol #

type ShowList arg arg1 :: Symbol #

(SShow EqualityCheck, SShow HashFunc) => SShow Via Source # 
Instance details

Defined in StreamPatch.Patch.Compare

Methods

sShowsPrec :: forall (t1 :: Natural) (t2 :: Via) (t3 :: Symbol). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply ShowsPrecSym0 t1) t2) t3) #

sShow_ :: forall (t :: Via). Sing t -> Sing (Apply Show_Sym0 t) #

sShowList :: forall (t1 :: [Via]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply ShowListSym0 t1) t2) #

(SDecide EqualityCheck, SDecide HashFunc) => TestCoercion SVia Source # 
Instance details

Defined in StreamPatch.Patch.Compare

Methods

testCoercion :: forall (a :: k) (b :: k). SVia a -> SVia b -> Maybe (Coercion a b) #

(SDecide EqualityCheck, SDecide HashFunc) => TestEquality SVia Source # 
Instance details

Defined in StreamPatch.Patch.Compare

Methods

testEquality :: forall (a :: k) (b :: k). SVia a -> SVia b -> Maybe (a :~: b) #

SingI 'ViaSize Source # 
Instance details

Defined in StreamPatch.Patch.Compare

Methods

sing :: Sing 'ViaSize #

SingI1 'ViaEq Source # 
Instance details

Defined in StreamPatch.Patch.Compare

Methods

liftSing :: forall (x :: k1). Sing x -> Sing ('ViaEq x) #

SingI1 'ViaDigest Source # 
Instance details

Defined in StreamPatch.Patch.Compare

Methods

liftSing :: forall (x :: k1). Sing x -> Sing ('ViaDigest x) #

SingI n => SingI ('ViaDigest n :: Via) Source # 
Instance details

Defined in StreamPatch.Patch.Compare

Methods

sing :: Sing ('ViaDigest n) #

SingI n => SingI ('ViaEq n :: Via) Source # 
Instance details

Defined in StreamPatch.Patch.Compare

Methods

sing :: Sing ('ViaEq n) #

SingI ViaEqSym0 Source # 
Instance details

Defined in StreamPatch.Patch.Compare

Methods

sing :: Sing ViaEqSym0 #

SingI ViaDigestSym0 Source # 
Instance details

Defined in StreamPatch.Patch.Compare

SuppressUnusedWarnings ViaEqSym0 Source # 
Instance details

Defined in StreamPatch.Patch.Compare

SuppressUnusedWarnings ViaDigestSym0 Source # 
Instance details

Defined in StreamPatch.Patch.Compare

SuppressUnusedWarnings TFHelper_6989586621679180946Sym0 Source # 
Instance details

Defined in StreamPatch.Patch.Compare

SuppressUnusedWarnings ShowsPrec_6989586621679180922Sym0 Source # 
Instance details

Defined in StreamPatch.Patch.Compare

SuppressUnusedWarnings (ShowsPrec_6989586621679180922Sym1 a6989586621679180934 :: TyFun Via (Symbol ~> Symbol) -> Type) Source # 
Instance details

Defined in StreamPatch.Patch.Compare

SuppressUnusedWarnings (TFHelper_6989586621679180946Sym1 a6989586621679180951 :: TyFun Via Bool -> Type) Source # 
Instance details

Defined in StreamPatch.Patch.Compare

type Rep Via Source # 
Instance details

Defined in StreamPatch.Patch.Compare

type Rep Via = D1 ('MetaData "Via" "StreamPatch.Patch.Compare" "bytepatch-0.4.1-inplace" 'False) (C1 ('MetaCons "ViaEq" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 EqualityCheck)) :+: (C1 ('MetaCons "ViaSize" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ViaDigest" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 HashFunc))))
type Demote Via Source # 
Instance details

Defined in StreamPatch.Patch.Compare

type Demote Via = Via
type Sing Source # 
Instance details

Defined in StreamPatch.Patch.Compare

type Sing = SVia
type Show_ (arg :: Via) Source # 
Instance details

Defined in StreamPatch.Patch.Compare

type Show_ (arg :: Via) = Apply (Show__6989586621680009330Sym0 :: TyFun Via Symbol -> Type) arg
type (arg :: Via) /= (arg1 :: Via) Source # 
Instance details

Defined in StreamPatch.Patch.Compare

type (arg :: Via) /= (arg1 :: Via) = Apply (Apply (TFHelper_6989586621679137069Sym0 :: TyFun Via (Via ~> Bool) -> Type) arg) arg1
type (a1 :: Via) == (a2 :: Via) Source # 
Instance details

Defined in StreamPatch.Patch.Compare

type (a1 :: Via) == (a2 :: Via) = Apply (Apply TFHelper_6989586621679180946Sym0 a1) a2
type ShowList (arg :: [Via]) arg1 Source # 
Instance details

Defined in StreamPatch.Patch.Compare

type ShowList (arg :: [Via]) arg1 = Apply (Apply (ShowList_6989586621680009344Sym0 :: TyFun [Via] (Symbol ~> Symbol) -> Type) arg) arg1
type Apply ViaEqSym0 (a6989586621679180915 :: EqualityCheck) Source # 
Instance details

Defined in StreamPatch.Patch.Compare

type Apply ViaEqSym0 (a6989586621679180915 :: EqualityCheck) = 'ViaEq a6989586621679180915
type Apply ViaDigestSym0 (a6989586621679180918 :: HashFunc) Source # 
Instance details

Defined in StreamPatch.Patch.Compare

type Apply ViaDigestSym0 (a6989586621679180918 :: HashFunc) = 'ViaDigest a6989586621679180918
type ShowsPrec a1 (a2 :: Via) a3 Source # 
Instance details

Defined in StreamPatch.Patch.Compare

type Apply (TFHelper_6989586621679180946Sym1 a6989586621679180951 :: TyFun Via Bool -> Type) (a6989586621679180952 :: Via) Source # 
Instance details

Defined in StreamPatch.Patch.Compare

type Apply (TFHelper_6989586621679180946Sym1 a6989586621679180951 :: TyFun Via Bool -> Type) (a6989586621679180952 :: Via) = TFHelper_6989586621679180946 a6989586621679180951 a6989586621679180952
type Apply TFHelper_6989586621679180946Sym0 (a6989586621679180951 :: Via) Source # 
Instance details

Defined in StreamPatch.Patch.Compare

type Apply TFHelper_6989586621679180946Sym0 (a6989586621679180951 :: Via) = TFHelper_6989586621679180946Sym1 a6989586621679180951
type Apply ShowsPrec_6989586621679180922Sym0 (a6989586621679180934 :: Natural) Source # 
Instance details

Defined in StreamPatch.Patch.Compare

type Apply ShowsPrec_6989586621679180922Sym0 (a6989586621679180934 :: Natural) = ShowsPrec_6989586621679180922Sym1 a6989586621679180934
type Apply (ShowsPrec_6989586621679180922Sym1 a6989586621679180934 :: TyFun Via (Symbol ~> Symbol) -> Type) (a6989586621679180935 :: Via) Source # 
Instance details

Defined in StreamPatch.Patch.Compare

type Apply (ShowsPrec_6989586621679180922Sym1 a6989586621679180934 :: TyFun Via (Symbol ~> Symbol) -> Type) (a6989586621679180935 :: Via) = ShowsPrec_6989586621679180922Sym2 a6989586621679180934 a6989586621679180935

type family ViaEqSym1 (a6989586621679180915 :: EqualityCheck) :: Via where ... Source #

Equations

ViaEqSym1 a6989586621679180915 = ViaEq a6989586621679180915 

data ViaEqSym0 :: (~>) EqualityCheck Via where Source #

Constructors

ViaEqSym0KindInference :: SameKind (Apply ViaEqSym0 arg) (ViaEqSym1 arg) => ViaEqSym0 a6989586621679180915 

Instances

Instances details
SingI ViaEqSym0 Source # 
Instance details

Defined in StreamPatch.Patch.Compare

Methods

sing :: Sing ViaEqSym0 #

SuppressUnusedWarnings ViaEqSym0 Source # 
Instance details

Defined in StreamPatch.Patch.Compare

type Apply ViaEqSym0 (a6989586621679180915 :: EqualityCheck) Source # 
Instance details

Defined in StreamPatch.Patch.Compare

type Apply ViaEqSym0 (a6989586621679180915 :: EqualityCheck) = 'ViaEq a6989586621679180915

type family ViaSizeSym0 :: Via where ... Source #

Equations

ViaSizeSym0 = ViaSize 

type family ViaDigestSym1 (a6989586621679180918 :: HashFunc) :: Via where ... Source #

Equations

ViaDigestSym1 a6989586621679180918 = ViaDigest a6989586621679180918 

data ViaDigestSym0 :: (~>) HashFunc Via where Source #

Constructors

ViaDigestSym0KindInference :: SameKind (Apply ViaDigestSym0 arg) (ViaDigestSym1 arg) => ViaDigestSym0 a6989586621679180918 

Instances

Instances details
SingI ViaDigestSym0 Source # 
Instance details

Defined in StreamPatch.Patch.Compare

SuppressUnusedWarnings ViaDigestSym0 Source # 
Instance details

Defined in StreamPatch.Patch.Compare

type Apply ViaDigestSym0 (a6989586621679180918 :: HashFunc) Source # 
Instance details

Defined in StreamPatch.Patch.Compare

type Apply ViaDigestSym0 (a6989586621679180918 :: HashFunc) = 'ViaDigest a6989586621679180918

type family ShowsPrec_6989586621679180922 (a :: Natural) (a :: Via) (a :: Symbol) :: Symbol where ... Source #

Equations

ShowsPrec_6989586621679180922 p_6989586621679180900 (ViaEq arg_6989586621679180902) a_6989586621679180924 = Apply (Apply (Apply ShowParenSym0 (Apply (Apply (>@#@$) p_6989586621679180900) (FromInteger 10))) (Apply (Apply (.@#@$) (Apply ShowStringSym0 (FromString "ViaEq "))) (Apply (Apply ShowsPrecSym0 (FromInteger 11)) arg_6989586621679180902))) a_6989586621679180924 
ShowsPrec_6989586621679180922 _ ViaSize a_6989586621679180926 = Apply (Apply ShowStringSym0 (FromString "ViaSize")) a_6989586621679180926 
ShowsPrec_6989586621679180922 p_6989586621679180900 (ViaDigest arg_6989586621679180904) a_6989586621679180928 = Apply (Apply (Apply ShowParenSym0 (Apply (Apply (>@#@$) p_6989586621679180900) (FromInteger 10))) (Apply (Apply (.@#@$) (Apply ShowStringSym0 (FromString "ViaDigest "))) (Apply (Apply ShowsPrecSym0 (FromInteger 11)) arg_6989586621679180904))) a_6989586621679180928 

type family ShowsPrec_6989586621679180922Sym3 (a6989586621679180934 :: Natural) (a6989586621679180935 :: Via) (a6989586621679180936 :: Symbol) :: Symbol where ... Source #

Equations

ShowsPrec_6989586621679180922Sym3 a6989586621679180934 a6989586621679180935 a6989586621679180936 = ShowsPrec_6989586621679180922 a6989586621679180934 a6989586621679180935 a6989586621679180936 

data ShowsPrec_6989586621679180922Sym2 (a6989586621679180934 :: Natural) (a6989586621679180935 :: Via) :: (~>) Symbol Symbol where Source #

Constructors

ShowsPrec_6989586621679180922Sym2KindInference :: SameKind (Apply (ShowsPrec_6989586621679180922Sym2 a6989586621679180934 a6989586621679180935) arg) (ShowsPrec_6989586621679180922Sym3 a6989586621679180934 a6989586621679180935 arg) => ShowsPrec_6989586621679180922Sym2 a6989586621679180934 a6989586621679180935 a6989586621679180936 

Instances

Instances details
SuppressUnusedWarnings (ShowsPrec_6989586621679180922Sym2 a6989586621679180934 a6989586621679180935 :: TyFun Symbol Symbol -> Type) Source # 
Instance details

Defined in StreamPatch.Patch.Compare

type Apply (ShowsPrec_6989586621679180922Sym2 a6989586621679180934 a6989586621679180935 :: TyFun Symbol Symbol -> Type) (a6989586621679180936 :: Symbol) Source # 
Instance details

Defined in StreamPatch.Patch.Compare

type Apply (ShowsPrec_6989586621679180922Sym2 a6989586621679180934 a6989586621679180935 :: TyFun Symbol Symbol -> Type) (a6989586621679180936 :: Symbol) = ShowsPrec_6989586621679180922 a6989586621679180934 a6989586621679180935 a6989586621679180936

data ShowsPrec_6989586621679180922Sym1 (a6989586621679180934 :: Natural) :: (~>) Via ((~>) Symbol Symbol) where Source #

Constructors

ShowsPrec_6989586621679180922Sym1KindInference :: SameKind (Apply (ShowsPrec_6989586621679180922Sym1 a6989586621679180934) arg) (ShowsPrec_6989586621679180922Sym2 a6989586621679180934 arg) => ShowsPrec_6989586621679180922Sym1 a6989586621679180934 a6989586621679180935 

Instances

Instances details
SuppressUnusedWarnings (ShowsPrec_6989586621679180922Sym1 a6989586621679180934 :: TyFun Via (Symbol ~> Symbol) -> Type) Source # 
Instance details

Defined in StreamPatch.Patch.Compare

type Apply (ShowsPrec_6989586621679180922Sym1 a6989586621679180934 :: TyFun Via (Symbol ~> Symbol) -> Type) (a6989586621679180935 :: Via) Source # 
Instance details

Defined in StreamPatch.Patch.Compare

type Apply (ShowsPrec_6989586621679180922Sym1 a6989586621679180934 :: TyFun Via (Symbol ~> Symbol) -> Type) (a6989586621679180935 :: Via) = ShowsPrec_6989586621679180922Sym2 a6989586621679180934 a6989586621679180935

type family TFHelper_6989586621679180946Sym2 (a6989586621679180951 :: Via) (a6989586621679180952 :: Via) :: Bool where ... Source #

Equations

TFHelper_6989586621679180946Sym2 a6989586621679180951 a6989586621679180952 = TFHelper_6989586621679180946 a6989586621679180951 a6989586621679180952 

data TFHelper_6989586621679180946Sym1 (a6989586621679180951 :: Via) :: (~>) Via Bool where Source #

Constructors

TFHelper_6989586621679180946Sym1KindInference :: SameKind (Apply (TFHelper_6989586621679180946Sym1 a6989586621679180951) arg) (TFHelper_6989586621679180946Sym2 a6989586621679180951 arg) => TFHelper_6989586621679180946Sym1 a6989586621679180951 a6989586621679180952 

Instances

Instances details
SuppressUnusedWarnings (TFHelper_6989586621679180946Sym1 a6989586621679180951 :: TyFun Via Bool -> Type) Source # 
Instance details

Defined in StreamPatch.Patch.Compare

type Apply (TFHelper_6989586621679180946Sym1 a6989586621679180951 :: TyFun Via Bool -> Type) (a6989586621679180952 :: Via) Source # 
Instance details

Defined in StreamPatch.Patch.Compare

type Apply (TFHelper_6989586621679180946Sym1 a6989586621679180951 :: TyFun Via Bool -> Type) (a6989586621679180952 :: Via) = TFHelper_6989586621679180946 a6989586621679180951 a6989586621679180952

data SVia :: Via -> Type where Source #

Constructors

SViaEq :: forall (n :: EqualityCheck). (Sing n) -> SVia (ViaEq n :: Via) 
SViaSize :: SVia (ViaSize :: Via) 
SViaDigest :: forall (n :: HashFunc). (Sing n) -> SVia (ViaDigest n :: Via) 

Instances

Instances details
(SDecide EqualityCheck, SDecide HashFunc) => TestCoercion SVia Source # 
Instance details

Defined in StreamPatch.Patch.Compare

Methods

testCoercion :: forall (a :: k) (b :: k). SVia a -> SVia b -> Maybe (Coercion a b) #

(SDecide EqualityCheck, SDecide HashFunc) => TestEquality SVia Source # 
Instance details

Defined in StreamPatch.Patch.Compare

Methods

testEquality :: forall (a :: k) (b :: k). SVia a -> SVia b -> Maybe (a :~: b) #

(ShowSing EqualityCheck, ShowSing HashFunc) => Show (SVia z) Source # 
Instance details

Defined in StreamPatch.Patch.Compare

Methods

showsPrec :: Int -> SVia z -> ShowS #

show :: SVia z -> String #

showList :: [SVia z] -> ShowS #

data Meta (v :: Via) a Source #

Constructors

Meta 

Fields

Instances

Instances details
SingI v => Foldable (Meta v) Source # 
Instance details

Defined in StreamPatch.Patch.Compare

Methods

fold :: Monoid m => Meta v m -> m #

foldMap :: Monoid m => (a -> m) -> Meta v a -> m #

foldMap' :: Monoid m => (a -> m) -> Meta v a -> m #

foldr :: (a -> b -> b) -> b -> Meta v a -> b #

foldr' :: (a -> b -> b) -> b -> Meta v a -> b #

foldl :: (b -> a -> b) -> b -> Meta v a -> b #

foldl' :: (b -> a -> b) -> b -> Meta v a -> b #

foldr1 :: (a -> a -> a) -> Meta v a -> a #

foldl1 :: (a -> a -> a) -> Meta v a -> a #

toList :: Meta v a -> [a] #

null :: Meta v a -> Bool #

length :: Meta v a -> Int #

elem :: Eq a => a -> Meta v a -> Bool #

maximum :: Ord a => Meta v a -> a #

minimum :: Ord a => Meta v a -> a #

sum :: Num a => Meta v a -> a #

product :: Num a => Meta v a -> a #

SingI v => Traversable (Meta v) Source # 
Instance details

Defined in StreamPatch.Patch.Compare

Methods

traverse :: Applicative f => (a -> f b) -> Meta v a -> f (Meta v b) #

sequenceA :: Applicative f => Meta v (f a) -> f (Meta v a) #

mapM :: Monad m => (a -> m b) -> Meta v a -> m (Meta v b) #

sequence :: Monad m => Meta v (m a) -> m (Meta v a) #

SingI v => Functor (Meta v) Source # 
Instance details

Defined in StreamPatch.Patch.Compare

Methods

fmap :: (a -> b) -> Meta v a -> Meta v b #

(<$) :: a -> Meta v b -> Meta v a #

FromJSON (CompareRep v a) => FromJSON (Meta v a) Source # 
Instance details

Defined in StreamPatch.Patch.Compare

Methods

parseJSON :: Value -> Parser (Meta v a) #

parseJSONList :: Value -> Parser [Meta v a] #

ToJSON (CompareRep v a) => ToJSON (Meta v a) Source # 
Instance details

Defined in StreamPatch.Patch.Compare

Methods

toJSON :: Meta v a -> Value #

toEncoding :: Meta v a -> Encoding #

toJSONList :: [Meta v a] -> Value #

toEncodingList :: [Meta v a] -> Encoding #

Generic (Meta v a) Source # 
Instance details

Defined in StreamPatch.Patch.Compare

Associated Types

type Rep (Meta v a) :: Type -> Type #

Methods

from :: Meta v a -> Rep (Meta v a) x #

to :: Rep (Meta v a) x -> Meta v a #

Show (CompareRep v a) => Show (Meta v a) Source # 
Instance details

Defined in StreamPatch.Patch.Compare

Methods

showsPrec :: Int -> Meta v a -> ShowS #

show :: Meta v a -> String #

showList :: [Meta v a] -> ShowS #

Eq (CompareRep v a) => Eq (Meta v a) Source # 
Instance details

Defined in StreamPatch.Patch.Compare

Methods

(==) :: Meta v a -> Meta v a -> Bool #

(/=) :: Meta v a -> Meta v a -> Bool #

type Rep (Meta v a) Source # 
Instance details

Defined in StreamPatch.Patch.Compare

type Rep (Meta v a) = D1 ('MetaData "Meta" "StreamPatch.Patch.Compare" "bytepatch-0.4.1-inplace" 'False) (C1 ('MetaCons "Meta" 'PrefixI 'True) (S1 ('MetaSel ('Just "mCompare") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (CompareRep v a)))))

type family CompareRep (v :: Via) a where ... Source #

newtype Digest (h :: HashFunc) a Source #

The resulting digest from hashing some data using the given hash function.

TODO As of 2022, most good cryptographic hash functions produce digest sizes between 256-512 bits. That's 32-64 bytes. So I want to use a ShortByteString, but the BLAKE3 library uses the memory library, which I can't figure out. I bet it'd be more efficient. So, I'm polymorphising in preparation.

Constructors

Digest 

Fields

Instances

Instances details
(l ~ HashFuncLabel h, KnownSymbol l) => FromJSON (Digest h ByteString) Source # 
Instance details

Defined in StreamPatch.Patch.Compare

(l ~ HashFuncLabel h, KnownSymbol l) => ToJSON (Digest h ByteString) Source #

Add a digest: prefix to better separate from regular text.

Instance details

Defined in StreamPatch.Patch.Compare

Generic (Digest h a) Source # 
Instance details

Defined in StreamPatch.Patch.Compare

Associated Types

type Rep (Digest h a) :: Type -> Type #

Methods

from :: Digest h a -> Rep (Digest h a) x #

to :: Rep (Digest h a) x -> Digest h a #

Show a => Show (Digest h a) Source # 
Instance details

Defined in StreamPatch.Patch.Compare

Methods

showsPrec :: Int -> Digest h a -> ShowS #

show :: Digest h a -> String #

showList :: [Digest h a] -> ShowS #

Eq a => Eq (Digest h a) Source # 
Instance details

Defined in StreamPatch.Patch.Compare

Methods

(==) :: Digest h a -> Digest h a -> Bool #

(/=) :: Digest h a -> Digest h a -> Bool #

type Rep (Digest h a) Source # 
Instance details

Defined in StreamPatch.Patch.Compare

type Rep (Digest h a) = D1 ('MetaData "Digest" "StreamPatch.Patch.Compare" "bytepatch-0.4.1-inplace" 'True) (C1 ('MetaCons "Digest" 'PrefixI 'True) (S1 ('MetaSel ('Just "getDigest") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))

type family HashFuncLabel (h :: HashFunc) where ... Source #

Equations

HashFuncLabel 'B3 = "b3" 
HashFuncLabel 'SHA256 = "sha256" 
HashFuncLabel 'MD5 = "md5" 

hashFuncLabel :: forall h l. (l ~ HashFuncLabel h, KnownSymbol l) => Text Source #

prettyDigest :: forall h a l. (l ~ HashFuncLabel h, KnownSymbol l) => (a -> [Word8]) -> Digest h a -> Text Source #

Pretty print a hash like hashfunc:123abc.

parseDigest :: forall h l e s m. (l ~ HashFuncLabel h, KnownSymbol l, MonadParsec e s m, Token s ~ Char, Tokens s ~ Text) => m (Digest h ByteString) Source #

compareTo :: forall v a. Compare v a => CompareRep v a -> a -> Maybe String Source #

class SwapCompare a (vFrom :: Via) (vTo :: Via) where Source #

Methods

swapCompare :: CompareRep vFrom a -> Either String (CompareRep vTo a) Source #

Instances

Instances details
SwapCompare a v v Source # 
Instance details

Defined in StreamPatch.Patch.Compare

SwapCompare ByteString ('ViaEq 'Exact) ('ViaDigest 'B3) Source # 
Instance details

Defined in StreamPatch.Patch.Compare