patch-0.0.0.0: TODO

Safe HaskellSafe
LanguageHaskell98

Data.Functor.Misc

Contents

Description

This module provides types and functions with no particular theme, but which are relevant to the use of Functor-based datastructures like DMap.

Synopsis

Const2

data Const2 :: * -> x -> x -> * where Source #

Const2 stores a value of a given type k and ensures that a particular type v is always given for the last type parameter

Constructors

Const2 :: k -> Const2 k v v 
Instances
Ord k2 => GCompare (Const2 k2 v :: k1 -> Type) Source # 
Instance details

Defined in Data.Functor.Misc

Methods

gcompare :: Const2 k2 v a -> Const2 k2 v b -> GOrdering a b #

Eq k2 => GEq (Const2 k2 v :: k1 -> Type) Source # 
Instance details

Defined in Data.Functor.Misc

Methods

geq :: Const2 k2 v a -> Const2 k2 v b -> Maybe (a :~: b) #

Show k2 => GShow (Const2 k2 v :: k1 -> Type) Source # 
Instance details

Defined in Data.Functor.Misc

Methods

gshowsPrec :: Int -> Const2 k2 v a -> ShowS #

Eq k => Eq (Const2 k v v') Source # 
Instance details

Defined in Data.Functor.Misc

Methods

(==) :: Const2 k v v' -> Const2 k v v' -> Bool #

(/=) :: Const2 k v v' -> Const2 k v v' -> Bool #

Ord k => Ord (Const2 k v v') Source # 
Instance details

Defined in Data.Functor.Misc

Methods

compare :: Const2 k v v' -> Const2 k v v' -> Ordering #

(<) :: Const2 k v v' -> Const2 k v v' -> Bool #

(<=) :: Const2 k v v' -> Const2 k v v' -> Bool #

(>) :: Const2 k v v' -> Const2 k v v' -> Bool #

(>=) :: Const2 k v v' -> Const2 k v v' -> Bool #

max :: Const2 k v v' -> Const2 k v v' -> Const2 k v v' #

min :: Const2 k v v' -> Const2 k v v' -> Const2 k v v' #

Read k => Read (Const2 k v v) Source # 
Instance details

Defined in Data.Functor.Misc

Methods

readsPrec :: Int -> ReadS (Const2 k v v) #

readList :: ReadS [Const2 k v v] #

readPrec :: ReadPrec (Const2 k v v) #

readListPrec :: ReadPrec [Const2 k v v] #

Show k => Show (Const2 k v v') Source # 
Instance details

Defined in Data.Functor.Misc

Methods

showsPrec :: Int -> Const2 k v v' -> ShowS #

show :: Const2 k v v' -> String #

showList :: [Const2 k v v'] -> ShowS #

unConst2 :: Const2 k v v' -> k Source #

Extract the value from a Const2

dmapToMap :: DMap (Const2 k v) Identity -> Map k v Source #

Convert a DMap to a regular Map

dmapToMapWith :: (f v -> v') -> DMap (Const2 k v) f -> Map k v' Source #

Convert a DMap to a regular Map, applying the given function to remove the wrapping Functor

mapToDMap :: Map k v -> DMap (Const2 k v) Identity Source #

Convert a regular Map to a DMap

weakenDMapWith :: (forall a. v a -> v') -> DMap k v -> Map (Some k) v' Source #

Convert a DMap to a regular Map by forgetting the types associated with the keys, using a function to remove the wrapping Functor

WrapArg

data WrapArg :: (k -> *) -> (k -> *) -> * -> * where Source #

WrapArg can be used to tag a value in one functor with a type representing another functor. This was primarily used with dependent-map < 0.2, in which the value type was not wrapped in a separate functor.

Constructors

WrapArg :: f a -> WrapArg g f (g a) 
Instances
GCompare f => GCompare (WrapArg g f :: Type -> Type) Source # 
Instance details

Defined in Data.Functor.Misc

Methods

gcompare :: WrapArg g f a -> WrapArg g f b -> GOrdering a b #

GEq f => GEq (WrapArg g f :: Type -> Type) Source # 
Instance details

Defined in Data.Functor.Misc

Methods

geq :: WrapArg g f a -> WrapArg g f b -> Maybe (a :~: b) #

Eq (f a) => Eq (WrapArg g f (g' a)) Source # 
Instance details

Defined in Data.Functor.Misc

Methods

(==) :: WrapArg g f (g' a) -> WrapArg g f (g' a) -> Bool #

(/=) :: WrapArg g f (g' a) -> WrapArg g f (g' a) -> Bool #

Ord (f a) => Ord (WrapArg g f (g' a)) Source # 
Instance details

Defined in Data.Functor.Misc

Methods

compare :: WrapArg g f (g' a) -> WrapArg g f (g' a) -> Ordering #

(<) :: WrapArg g f (g' a) -> WrapArg g f (g' a) -> Bool #

(<=) :: WrapArg g f (g' a) -> WrapArg g f (g' a) -> Bool #

(>) :: WrapArg g f (g' a) -> WrapArg g f (g' a) -> Bool #

(>=) :: WrapArg g f (g' a) -> WrapArg g f (g' a) -> Bool #

max :: WrapArg g f (g' a) -> WrapArg g f (g' a) -> WrapArg g f (g' a) #

min :: WrapArg g f (g' a) -> WrapArg g f (g' a) -> WrapArg g f (g' a) #

Read (f a) => Read (WrapArg g f (g a)) Source # 
Instance details

Defined in Data.Functor.Misc

Methods

readsPrec :: Int -> ReadS (WrapArg g f (g a)) #

readList :: ReadS [WrapArg g f (g a)] #

readPrec :: ReadPrec (WrapArg g f (g a)) #

readListPrec :: ReadPrec [WrapArg g f (g a)] #

Show (f a) => Show (WrapArg g f (g' a)) Source # 
Instance details

Defined in Data.Functor.Misc

Methods

showsPrec :: Int -> WrapArg g f (g' a) -> ShowS #

show :: WrapArg g f (g' a) -> String #

showList :: [WrapArg g f (g' a)] -> ShowS #

Convenience functions for DMap

mapWithFunctorToDMap :: Map k (f v) -> DMap (Const2 k v) f Source #

Convert a regular Map, where the values are already wrapped in a functor, to a DMap

intMapWithFunctorToDMap :: IntMap (f v) -> DMap (Const2 Key v) f Source #

Convert a regular IntMap, where the values are already wrapped in a functor, to a DMap

mapKeyValuePairsMonotonic :: (DSum k v -> DSum k' v') -> DMap k v -> DMap k' v' Source #

Map over all key/value pairs in a DMap, potentially altering the key as well as the value. The provided function MUST preserve the ordering of the keys, or the resulting DMap will be malformed.

combineDMapsWithKey :: forall f g h i. GCompare f => (forall a. f a -> These (g a) (h a) -> i a) -> DMap f g -> DMap f h -> DMap f i Source #

Union two DMaps of different types, yielding another type. Each key that is present in either input map will be present in the output.

data EitherTag l r a where Source #

Tag type for Either to use it as a DSum.

Constructors

LeftTag :: EitherTag l r l 
RightTag :: EitherTag l r r 
Instances
GCompare (EitherTag l r :: k -> Type) Source # 
Instance details

Defined in Data.Functor.Misc

Methods

gcompare :: EitherTag l r a -> EitherTag l r b -> GOrdering a b #

GEq (EitherTag l r :: k -> Type) Source # 
Instance details

Defined in Data.Functor.Misc

Methods

geq :: EitherTag l r a -> EitherTag l r b -> Maybe (a :~: b) #

GShow (EitherTag l r :: k -> Type) Source # 
Instance details

Defined in Data.Functor.Misc

Methods

gshowsPrec :: Int -> EitherTag l r a -> ShowS #

Eq (EitherTag l r a) Source # 
Instance details

Defined in Data.Functor.Misc

Methods

(==) :: EitherTag l r a -> EitherTag l r a -> Bool #

(/=) :: EitherTag l r a -> EitherTag l r a -> Bool #

Ord (EitherTag l r a) Source # 
Instance details

Defined in Data.Functor.Misc

Methods

compare :: EitherTag l r a -> EitherTag l r a -> Ordering #

(<) :: EitherTag l r a -> EitherTag l r a -> Bool #

(<=) :: EitherTag l r a -> EitherTag l r a -> Bool #

(>) :: EitherTag l r a -> EitherTag l r a -> Bool #

(>=) :: EitherTag l r a -> EitherTag l r a -> Bool #

max :: EitherTag l r a -> EitherTag l r a -> EitherTag l r a #

min :: EitherTag l r a -> EitherTag l r a -> EitherTag l r a #

Show (EitherTag l r a) Source # 
Instance details

Defined in Data.Functor.Misc

Methods

showsPrec :: Int -> EitherTag l r a -> ShowS #

show :: EitherTag l r a -> String #

showList :: [EitherTag l r a] -> ShowS #

dmapToThese :: DMap (EitherTag a b) Identity -> Maybe (These a b) Source #

Extract the values of a DMap of EitherTags.

eitherToDSum :: Either a b -> DSum (EitherTag a b) Identity Source #

Convert Either to a DSum. Inverse of dsumToEither.

dsumToEither :: DSum (EitherTag a b) Identity -> Either a b Source #

Convert DSum to Either. Inverse of eitherToDSum.

newtype ComposeMaybe f a Source #

We can't use Compose Maybe instead of ComposeMaybe, because that would make the f parameter have a nominal type role. We need f to be representational so that we can use safe coerce.

Constructors

ComposeMaybe 

Fields

Instances
Functor f => Functor (ComposeMaybe f) Source # 
Instance details

Defined in Data.Functor.Misc

Methods

fmap :: (a -> b) -> ComposeMaybe f a -> ComposeMaybe f b #

(<$) :: a -> ComposeMaybe f b -> ComposeMaybe f a #

Eq (f a) => Eq (ComposeMaybe f a) Source # 
Instance details

Defined in Data.Functor.Misc

Methods

(==) :: ComposeMaybe f a -> ComposeMaybe f a -> Bool #

(/=) :: ComposeMaybe f a -> ComposeMaybe f a -> Bool #

Ord (f a) => Ord (ComposeMaybe f a) Source # 
Instance details

Defined in Data.Functor.Misc

Show (f a) => Show (ComposeMaybe f a) Source # 
Instance details

Defined in Data.Functor.Misc