Safe Haskell | None |
---|---|
Language | Haskell98 |
Synopsis
- data Const2 :: * -> x -> x -> * where
- unConst2 :: Const2 k v v' -> k
- dmapToMap :: DMap (Const2 k v) Identity -> Map k v
- dmapToIntMap :: DMap (Const2 Key v) Identity -> IntMap v
- dmapToMapWith :: (f v -> v') -> DMap (Const2 k v) f -> Map k v'
- mapToDMap :: Map k v -> DMap (Const2 k v) Identity
- weakenDMapWith :: (forall a. v a -> v') -> DMap k v -> Map (Some k) v'
- data WrapArg :: (k -> *) -> (k -> *) -> * -> * where
- mapWithFunctorToDMap :: Map k (f v) -> DMap (Const2 k v) f
- intMapWithFunctorToDMap :: IntMap (f v) -> DMap (Const2 Key v) f
- mapKeyValuePairsMonotonic :: (DSum k v -> DSum k' v') -> DMap k v -> DMap k' v'
- 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
- data EitherTag l r a where
- dmapToThese :: DMap (EitherTag a b) Identity -> Maybe (These a b)
- eitherToDSum :: Either a b -> DSum (EitherTag a b) Identity
- dsumToEither :: DSum (EitherTag a b) Identity -> Either a b
- sequenceDmap :: Applicative t => DMap f t -> t (DMap f Identity)
- wrapDMap :: (forall a. a -> f a) -> DMap k Identity -> DMap k f
- rewrapDMap :: (forall (a :: *). f a -> g a) -> DMap k f -> DMap k g
- unwrapDMap :: (forall a. f a -> a) -> DMap k f -> DMap k Identity
- unwrapDMapMaybe :: GCompare k => (forall a. f a -> Maybe a) -> DMap k f -> DMap k Identity
- extractFunctorDMap :: DMap (Const2 k (f v)) Identity -> DMap (Const2 k v) f
- newtype ComposeMaybe f a = ComposeMaybe {
- getComposeMaybe :: Maybe (f a)
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
Instances
Ord k2 => GCompare (Const2 k2 v :: k1 -> Type) Source # | |
Eq k2 => GEq (Const2 k2 v :: k1 -> Type) Source # | |
Show k2 => GShow (Const2 k2 v :: k1 -> Type) Source # | |
Defined in Data.Functor.Misc gshowsPrec :: Int -> Const2 k2 v a -> ShowS # | |
(Show k2, Show (f v)) => ShowTag (Const2 k2 v :: k1 -> Type) (f :: k1 -> Type) Source # | |
Defined in Data.Functor.Misc showTaggedPrec :: Const2 k2 v a -> Int -> f a -> ShowS # | |
Eq k => Eq (Const2 k v v') Source # | |
Ord k => Ord (Const2 k v v') Source # | |
Defined in Data.Functor.Misc 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 # | |
Read k => Read (Const2 k v v) Source # | |
Show k => Show (Const2 k v v') Source # | |
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.
Instances
GCompare f => GCompare (WrapArg g f :: Type -> Type) Source # | |
GEq f => GEq (WrapArg g f :: Type -> Type) Source # | |
Eq (f a) => Eq (WrapArg g f (g' a)) Source # | |
Ord (f a) => Ord (WrapArg g f (g' a)) Source # | |
Defined in Data.Functor.Misc 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 # | |
Show (f a) => Show (WrapArg g f (g' a)) Source # | |
Convenience functions for DMap
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 DMap
s 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 #
Instances
GCompare (EitherTag l r :: k -> Type) Source # | |
GEq (EitherTag l r :: k -> Type) Source # | |
GShow (EitherTag l r :: k -> Type) Source # | |
Defined in Data.Functor.Misc gshowsPrec :: Int -> EitherTag l r a -> ShowS # | |
(Show l, Show r) => ShowTag (EitherTag l r :: Type -> Type) Identity Source # | |
Defined in Data.Functor.Misc | |
Eq (EitherTag l r a) Source # | |
Ord (EitherTag l r a) Source # | |
Defined in Data.Functor.Misc 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 # | |
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
.
Deprecated functions
sequenceDmap :: Applicative t => DMap f t -> t (DMap f Identity) Source #
Deprecated: Use 'Data.Dependent.Map.traverseWithKey (_ -> fmap Identity)' instead
Run the actions contained in the DMap
wrapDMap :: (forall a. a -> f a) -> DMap k Identity -> DMap k f Source #
Deprecated: Use 'Data.Dependent.Map.map (f . runIdentity)' instead
Replace the Identity
functor for a DMap'
s values with a different functor
rewrapDMap :: (forall (a :: *). f a -> g a) -> DMap k f -> DMap k g Source #
Deprecated: Use map
instead
Replace one functor for a DMap'
s values with a different functor
unwrapDMap :: (forall a. f a -> a) -> DMap k f -> DMap k Identity Source #
Deprecated: Use 'Data.Dependent.Map.map (Identity . f)' instead
Replace one functor for a DMap'
s values with the Identity
functor
unwrapDMapMaybe :: GCompare k => (forall a. f a -> Maybe a) -> DMap k f -> DMap k Identity Source #
Deprecated: Use 'Data.Dependent.Map.mapMaybeWithKey (_ a -> fmap Identity $ f a)' instead
Like unwrapDMap
, but possibly delete some values from the DMap
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
.
ComposeMaybe | |
|