| Copyright | (C) 2013-2014 Richard Eisenberg Jan Stolarek |
|---|---|
| License | BSD-style (see LICENSE) |
| Maintainer | Ryan Scott |
| Stability | experimental |
| Portability | non-portable |
| Safe Haskell | None |
| Language | Haskell2010 |
Data.Singletons.Prelude.Maybe
Description
Defines functions and datatypes relating to the singleton for Maybe,
including a singletons version of all the definitions in Data.Maybe.
Because many of these definitions are produced by Template Haskell,
it is not possible to create proper Haddock documentation. Please look
up the corresponding operation in Data.Maybe. Also, please excuse
the apparent repeated variable names. This is due to an interaction
between Template Haskell and Haddock.
Synopsis
- type family Sing :: k -> Type
- data SMaybe :: forall a. Maybe a -> Type where
- maybe_ :: b -> (a -> b) -> Maybe a -> b
- type family Maybe_ (a :: b) (a :: (~>) a b) (a :: Maybe a) :: b where ...
- sMaybe_ :: forall b a (t :: b) (t :: (~>) a b) (t :: Maybe a). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply Maybe_Sym0 t) t) t :: b)
- type family IsJust (a :: Maybe a) :: Bool where ...
- sIsJust :: forall a (t :: Maybe a). Sing t -> Sing (Apply IsJustSym0 t :: Bool)
- type family IsNothing (a :: Maybe a) :: Bool where ...
- sIsNothing :: forall a (t :: Maybe a). Sing t -> Sing (Apply IsNothingSym0 t :: Bool)
- type family FromJust (a :: Maybe a) :: a where ...
- sFromJust :: forall a (t :: Maybe a). Sing t -> Sing (Apply FromJustSym0 t :: a)
- type family FromMaybe (a :: a) (a :: Maybe a) :: a where ...
- sFromMaybe :: forall a (t :: a) (t :: Maybe a). Sing t -> Sing t -> Sing (Apply (Apply FromMaybeSym0 t) t :: a)
- type family ListToMaybe (a :: [a]) :: Maybe a where ...
- sListToMaybe :: forall a (t :: [a]). Sing t -> Sing (Apply ListToMaybeSym0 t :: Maybe a)
- type family MaybeToList (a :: Maybe a) :: [a] where ...
- sMaybeToList :: forall a (t :: Maybe a). Sing t -> Sing (Apply MaybeToListSym0 t :: [a])
- type family CatMaybes (a :: [Maybe a]) :: [a] where ...
- sCatMaybes :: forall a (t :: [Maybe a]). Sing t -> Sing (Apply CatMaybesSym0 t :: [a])
- type family MapMaybe (a :: (~>) a (Maybe b)) (a :: [a]) :: [b] where ...
- sMapMaybe :: forall a b (t :: (~>) a (Maybe b)) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply MapMaybeSym0 t) t :: [b])
- type NothingSym0 = 'Nothing
- data JustSym0 :: forall (a3530822107858468865 :: Type). (~>) a3530822107858468865 (Maybe (a3530822107858468865 :: Type))
- type JustSym1 (t6989586621679315133 :: a3530822107858468865) = 'Just t6989586621679315133
- data Maybe_Sym0 :: forall b6989586621679514865 a6989586621679514866. (~>) b6989586621679514865 ((~>) ((~>) a6989586621679514866 b6989586621679514865) ((~>) (Maybe a6989586621679514866) b6989586621679514865))
- data Maybe_Sym1 (a6989586621679514883 :: b6989586621679514865) :: forall a6989586621679514866. (~>) ((~>) a6989586621679514866 b6989586621679514865) ((~>) (Maybe a6989586621679514866) b6989586621679514865)
- data Maybe_Sym2 (a6989586621679514883 :: b6989586621679514865) (a6989586621679514884 :: (~>) a6989586621679514866 b6989586621679514865) :: (~>) (Maybe a6989586621679514866) b6989586621679514865
- type Maybe_Sym3 (a6989586621679514883 :: b6989586621679514865) (a6989586621679514884 :: (~>) a6989586621679514866 b6989586621679514865) (a6989586621679514885 :: Maybe a6989586621679514866) = Maybe_ a6989586621679514883 a6989586621679514884 a6989586621679514885
- data IsJustSym0 :: forall a6989586621679516295. (~>) (Maybe a6989586621679516295) Bool
- type IsJustSym1 (a6989586621679516493 :: Maybe a6989586621679516295) = IsJust a6989586621679516493
- data IsNothingSym0 :: forall a6989586621679516294. (~>) (Maybe a6989586621679516294) Bool
- type IsNothingSym1 (a6989586621679516491 :: Maybe a6989586621679516294) = IsNothing a6989586621679516491
- data FromJustSym0 :: forall a6989586621679516293. (~>) (Maybe a6989586621679516293) a6989586621679516293
- type FromJustSym1 (a6989586621679516488 :: Maybe a6989586621679516293) = FromJust a6989586621679516488
- data FromMaybeSym0 :: forall a6989586621679516292. (~>) a6989586621679516292 ((~>) (Maybe a6989586621679516292) a6989586621679516292)
- data FromMaybeSym1 (a6989586621679516478 :: a6989586621679516292) :: (~>) (Maybe a6989586621679516292) a6989586621679516292
- type FromMaybeSym2 (a6989586621679516478 :: a6989586621679516292) (a6989586621679516479 :: Maybe a6989586621679516292) = FromMaybe a6989586621679516478 a6989586621679516479
- data ListToMaybeSym0 :: forall a6989586621679516290. (~>) [a6989586621679516290] (Maybe a6989586621679516290)
- type ListToMaybeSym1 (a6989586621679516472 :: [a6989586621679516290]) = ListToMaybe a6989586621679516472
- data MaybeToListSym0 :: forall a6989586621679516291. (~>) (Maybe a6989586621679516291) [a6989586621679516291]
- type MaybeToListSym1 (a6989586621679516475 :: Maybe a6989586621679516291) = MaybeToList a6989586621679516475
- data CatMaybesSym0 :: forall a6989586621679516289. (~>) [Maybe a6989586621679516289] [a6989586621679516289]
- type CatMaybesSym1 (a6989586621679516467 :: [Maybe a6989586621679516289]) = CatMaybes a6989586621679516467
- data MapMaybeSym0 :: forall a6989586621679516287 b6989586621679516288. (~>) ((~>) a6989586621679516287 (Maybe b6989586621679516288)) ((~>) [a6989586621679516287] [b6989586621679516288])
- data MapMaybeSym1 (a6989586621679516448 :: (~>) a6989586621679516287 (Maybe b6989586621679516288)) :: (~>) [a6989586621679516287] [b6989586621679516288]
- type MapMaybeSym2 (a6989586621679516448 :: (~>) a6989586621679516287 (Maybe b6989586621679516288)) (a6989586621679516449 :: [a6989586621679516287]) = MapMaybe a6989586621679516448 a6989586621679516449
Documentation
type family Sing :: k -> Type Source #
The singleton kind-indexed type family.
Instances
data SMaybe :: forall a. Maybe a -> Type where Source #
Constructors
| SNothing :: SMaybe 'Nothing | |
| SJust :: forall a (n :: a). (Sing (n :: a)) -> SMaybe ('Just n) |
Singletons from Data.Maybe
sMaybe_ :: forall b a (t :: b) (t :: (~>) a b) (t :: Maybe a). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply Maybe_Sym0 t) t) t :: b) Source #
The preceding two definitions are derived from the function maybe in
Data.Maybe. The extra underscore is to avoid name clashes with the type
Maybe.
sIsNothing :: forall a (t :: Maybe a). Sing t -> Sing (Apply IsNothingSym0 t :: Bool) Source #
type family FromMaybe (a :: a) (a :: Maybe a) :: a where ... Source #
Equations
| FromMaybe d x = Case_6989586621679516484 d x x |
sFromMaybe :: forall a (t :: a) (t :: Maybe a). Sing t -> Sing t -> Sing (Apply (Apply FromMaybeSym0 t) t :: a) Source #
type family ListToMaybe (a :: [a]) :: Maybe a where ... Source #
Equations
| ListToMaybe '[] = NothingSym0 | |
| ListToMaybe ('(:) a _) = Apply JustSym0 a |
sListToMaybe :: forall a (t :: [a]). Sing t -> Sing (Apply ListToMaybeSym0 t :: Maybe a) Source #
type family MaybeToList (a :: Maybe a) :: [a] where ... Source #
Equations
| MaybeToList 'Nothing = '[] | |
| MaybeToList ('Just x) = Apply (Apply (:@#@$) x) '[] |
sMaybeToList :: forall a (t :: Maybe a). Sing t -> Sing (Apply MaybeToListSym0 t :: [a]) Source #
sCatMaybes :: forall a (t :: [Maybe a]). Sing t -> Sing (Apply CatMaybesSym0 t :: [a]) Source #
sMapMaybe :: forall a b (t :: (~>) a (Maybe b)) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply MapMaybeSym0 t) t :: [b]) Source #
Defunctionalization symbols
type NothingSym0 = 'Nothing Source #
data JustSym0 :: forall (a3530822107858468865 :: Type). (~>) a3530822107858468865 (Maybe (a3530822107858468865 :: Type)) Source #
Instances
| SingI (JustSym0 :: TyFun a (Maybe a) -> Type) Source # | |
| SuppressUnusedWarnings (JustSym0 :: TyFun a3530822107858468865 (Maybe a3530822107858468865) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Instances Methods suppressUnusedWarnings :: () Source # | |
| type Apply (JustSym0 :: TyFun a (Maybe a) -> Type) (t6989586621679315133 :: a) Source # | |
data Maybe_Sym0 :: forall b6989586621679514865 a6989586621679514866. (~>) b6989586621679514865 ((~>) ((~>) a6989586621679514866 b6989586621679514865) ((~>) (Maybe a6989586621679514866) b6989586621679514865)) Source #
Instances
| SingI (Maybe_Sym0 :: TyFun b ((a ~> b) ~> (Maybe a ~> b)) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Maybe Methods sing :: Sing Maybe_Sym0 Source # | |
| SuppressUnusedWarnings (Maybe_Sym0 :: TyFun b6989586621679514865 ((a6989586621679514866 ~> b6989586621679514865) ~> (Maybe a6989586621679514866 ~> b6989586621679514865)) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Maybe Methods suppressUnusedWarnings :: () Source # | |
| type Apply (Maybe_Sym0 :: TyFun b6989586621679514865 ((a6989586621679514866 ~> b6989586621679514865) ~> (Maybe a6989586621679514866 ~> b6989586621679514865)) -> Type) (a6989586621679514883 :: b6989586621679514865) Source # | |
Defined in Data.Singletons.Prelude.Maybe type Apply (Maybe_Sym0 :: TyFun b6989586621679514865 ((a6989586621679514866 ~> b6989586621679514865) ~> (Maybe a6989586621679514866 ~> b6989586621679514865)) -> Type) (a6989586621679514883 :: b6989586621679514865) = Maybe_Sym1 a6989586621679514883 a6989586621679514866 :: TyFun (a6989586621679514866 ~> b6989586621679514865) (Maybe a6989586621679514866 ~> b6989586621679514865) -> Type | |
data Maybe_Sym1 (a6989586621679514883 :: b6989586621679514865) :: forall a6989586621679514866. (~>) ((~>) a6989586621679514866 b6989586621679514865) ((~>) (Maybe a6989586621679514866) b6989586621679514865) Source #
Instances
| SingI d => SingI (Maybe_Sym1 d a :: TyFun (a ~> b) (Maybe a ~> b) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Maybe Methods sing :: Sing (Maybe_Sym1 d a) Source # | |
| SuppressUnusedWarnings (Maybe_Sym1 a6989586621679514883 a6989586621679514866 :: TyFun (a6989586621679514866 ~> b6989586621679514865) (Maybe a6989586621679514866 ~> b6989586621679514865) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Maybe Methods suppressUnusedWarnings :: () Source # | |
| type Apply (Maybe_Sym1 a6989586621679514883 a6989586621679514866 :: TyFun (a6989586621679514866 ~> b6989586621679514865) (Maybe a6989586621679514866 ~> b6989586621679514865) -> Type) (a6989586621679514884 :: a6989586621679514866 ~> b6989586621679514865) Source # | |
Defined in Data.Singletons.Prelude.Maybe type Apply (Maybe_Sym1 a6989586621679514883 a6989586621679514866 :: TyFun (a6989586621679514866 ~> b6989586621679514865) (Maybe a6989586621679514866 ~> b6989586621679514865) -> Type) (a6989586621679514884 :: a6989586621679514866 ~> b6989586621679514865) = Maybe_Sym2 a6989586621679514883 a6989586621679514884 | |
data Maybe_Sym2 (a6989586621679514883 :: b6989586621679514865) (a6989586621679514884 :: (~>) a6989586621679514866 b6989586621679514865) :: (~>) (Maybe a6989586621679514866) b6989586621679514865 Source #
Instances
| (SingI d1, SingI d2) => SingI (Maybe_Sym2 d1 d2 :: TyFun (Maybe a) b -> Type) Source # | |
Defined in Data.Singletons.Prelude.Maybe Methods sing :: Sing (Maybe_Sym2 d1 d2) Source # | |
| SuppressUnusedWarnings (Maybe_Sym2 a6989586621679514884 a6989586621679514883 :: TyFun (Maybe a6989586621679514866) b6989586621679514865 -> Type) Source # | |
Defined in Data.Singletons.Prelude.Maybe Methods suppressUnusedWarnings :: () Source # | |
| type Apply (Maybe_Sym2 a6989586621679514884 a6989586621679514883 :: TyFun (Maybe a) b -> Type) (a6989586621679514885 :: Maybe a) Source # | |
Defined in Data.Singletons.Prelude.Maybe | |
type Maybe_Sym3 (a6989586621679514883 :: b6989586621679514865) (a6989586621679514884 :: (~>) a6989586621679514866 b6989586621679514865) (a6989586621679514885 :: Maybe a6989586621679514866) = Maybe_ a6989586621679514883 a6989586621679514884 a6989586621679514885 Source #
data IsJustSym0 :: forall a6989586621679516295. (~>) (Maybe a6989586621679516295) Bool Source #
Instances
| SingI (IsJustSym0 :: TyFun (Maybe a) Bool -> Type) Source # | |
Defined in Data.Singletons.Prelude.Maybe Methods sing :: Sing IsJustSym0 Source # | |
| SuppressUnusedWarnings (IsJustSym0 :: TyFun (Maybe a6989586621679516295) Bool -> Type) Source # | |
Defined in Data.Singletons.Prelude.Maybe Methods suppressUnusedWarnings :: () Source # | |
| type Apply (IsJustSym0 :: TyFun (Maybe a) Bool -> Type) (a6989586621679516493 :: Maybe a) Source # | |
Defined in Data.Singletons.Prelude.Maybe | |
type IsJustSym1 (a6989586621679516493 :: Maybe a6989586621679516295) = IsJust a6989586621679516493 Source #
data IsNothingSym0 :: forall a6989586621679516294. (~>) (Maybe a6989586621679516294) Bool Source #
Instances
| SingI (IsNothingSym0 :: TyFun (Maybe a) Bool -> Type) Source # | |
Defined in Data.Singletons.Prelude.Maybe Methods sing :: Sing IsNothingSym0 Source # | |
| SuppressUnusedWarnings (IsNothingSym0 :: TyFun (Maybe a6989586621679516294) Bool -> Type) Source # | |
Defined in Data.Singletons.Prelude.Maybe Methods suppressUnusedWarnings :: () Source # | |
| type Apply (IsNothingSym0 :: TyFun (Maybe a) Bool -> Type) (a6989586621679516491 :: Maybe a) Source # | |
Defined in Data.Singletons.Prelude.Maybe | |
type IsNothingSym1 (a6989586621679516491 :: Maybe a6989586621679516294) = IsNothing a6989586621679516491 Source #
data FromJustSym0 :: forall a6989586621679516293. (~>) (Maybe a6989586621679516293) a6989586621679516293 Source #
Instances
| SingI (FromJustSym0 :: TyFun (Maybe a) a -> Type) Source # | |
Defined in Data.Singletons.Prelude.Maybe Methods sing :: Sing FromJustSym0 Source # | |
| SuppressUnusedWarnings (FromJustSym0 :: TyFun (Maybe a6989586621679516293) a6989586621679516293 -> Type) Source # | |
Defined in Data.Singletons.Prelude.Maybe Methods suppressUnusedWarnings :: () Source # | |
| type Apply (FromJustSym0 :: TyFun (Maybe a) a -> Type) (a6989586621679516488 :: Maybe a) Source # | |
Defined in Data.Singletons.Prelude.Maybe | |
type FromJustSym1 (a6989586621679516488 :: Maybe a6989586621679516293) = FromJust a6989586621679516488 Source #
data FromMaybeSym0 :: forall a6989586621679516292. (~>) a6989586621679516292 ((~>) (Maybe a6989586621679516292) a6989586621679516292) Source #
Instances
| SingI (FromMaybeSym0 :: TyFun a (Maybe a ~> a) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Maybe Methods sing :: Sing FromMaybeSym0 Source # | |
| SuppressUnusedWarnings (FromMaybeSym0 :: TyFun a6989586621679516292 (Maybe a6989586621679516292 ~> a6989586621679516292) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Maybe Methods suppressUnusedWarnings :: () Source # | |
| type Apply (FromMaybeSym0 :: TyFun a6989586621679516292 (Maybe a6989586621679516292 ~> a6989586621679516292) -> Type) (a6989586621679516478 :: a6989586621679516292) Source # | |
Defined in Data.Singletons.Prelude.Maybe type Apply (FromMaybeSym0 :: TyFun a6989586621679516292 (Maybe a6989586621679516292 ~> a6989586621679516292) -> Type) (a6989586621679516478 :: a6989586621679516292) = FromMaybeSym1 a6989586621679516478 | |
data FromMaybeSym1 (a6989586621679516478 :: a6989586621679516292) :: (~>) (Maybe a6989586621679516292) a6989586621679516292 Source #
Instances
| SingI d => SingI (FromMaybeSym1 d :: TyFun (Maybe a) a -> Type) Source # | |
Defined in Data.Singletons.Prelude.Maybe Methods sing :: Sing (FromMaybeSym1 d) Source # | |
| SuppressUnusedWarnings (FromMaybeSym1 a6989586621679516478 :: TyFun (Maybe a6989586621679516292) a6989586621679516292 -> Type) Source # | |
Defined in Data.Singletons.Prelude.Maybe Methods suppressUnusedWarnings :: () Source # | |
| type Apply (FromMaybeSym1 a6989586621679516478 :: TyFun (Maybe a) a -> Type) (a6989586621679516479 :: Maybe a) Source # | |
Defined in Data.Singletons.Prelude.Maybe | |
type FromMaybeSym2 (a6989586621679516478 :: a6989586621679516292) (a6989586621679516479 :: Maybe a6989586621679516292) = FromMaybe a6989586621679516478 a6989586621679516479 Source #
data ListToMaybeSym0 :: forall a6989586621679516290. (~>) [a6989586621679516290] (Maybe a6989586621679516290) Source #
Instances
| SingI (ListToMaybeSym0 :: TyFun [a] (Maybe a) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Maybe Methods | |
| SuppressUnusedWarnings (ListToMaybeSym0 :: TyFun [a6989586621679516290] (Maybe a6989586621679516290) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Maybe Methods suppressUnusedWarnings :: () Source # | |
| type Apply (ListToMaybeSym0 :: TyFun [a] (Maybe a) -> Type) (a6989586621679516472 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.Maybe type Apply (ListToMaybeSym0 :: TyFun [a] (Maybe a) -> Type) (a6989586621679516472 :: [a]) = ListToMaybe a6989586621679516472 | |
type ListToMaybeSym1 (a6989586621679516472 :: [a6989586621679516290]) = ListToMaybe a6989586621679516472 Source #
data MaybeToListSym0 :: forall a6989586621679516291. (~>) (Maybe a6989586621679516291) [a6989586621679516291] Source #
Instances
| SingI (MaybeToListSym0 :: TyFun (Maybe a) [a] -> Type) Source # | |
Defined in Data.Singletons.Prelude.Maybe Methods | |
| SuppressUnusedWarnings (MaybeToListSym0 :: TyFun (Maybe a6989586621679516291) [a6989586621679516291] -> Type) Source # | |
Defined in Data.Singletons.Prelude.Maybe Methods suppressUnusedWarnings :: () Source # | |
| type Apply (MaybeToListSym0 :: TyFun (Maybe a) [a] -> Type) (a6989586621679516475 :: Maybe a) Source # | |
Defined in Data.Singletons.Prelude.Maybe type Apply (MaybeToListSym0 :: TyFun (Maybe a) [a] -> Type) (a6989586621679516475 :: Maybe a) = MaybeToList a6989586621679516475 | |
type MaybeToListSym1 (a6989586621679516475 :: Maybe a6989586621679516291) = MaybeToList a6989586621679516475 Source #
data CatMaybesSym0 :: forall a6989586621679516289. (~>) [Maybe a6989586621679516289] [a6989586621679516289] Source #
Instances
| SingI (CatMaybesSym0 :: TyFun [Maybe a] [a] -> Type) Source # | |
Defined in Data.Singletons.Prelude.Maybe Methods sing :: Sing CatMaybesSym0 Source # | |
| SuppressUnusedWarnings (CatMaybesSym0 :: TyFun [Maybe a6989586621679516289] [a6989586621679516289] -> Type) Source # | |
Defined in Data.Singletons.Prelude.Maybe Methods suppressUnusedWarnings :: () Source # | |
| type Apply (CatMaybesSym0 :: TyFun [Maybe a] [a] -> Type) (a6989586621679516467 :: [Maybe a]) Source # | |
Defined in Data.Singletons.Prelude.Maybe | |
type CatMaybesSym1 (a6989586621679516467 :: [Maybe a6989586621679516289]) = CatMaybes a6989586621679516467 Source #
data MapMaybeSym0 :: forall a6989586621679516287 b6989586621679516288. (~>) ((~>) a6989586621679516287 (Maybe b6989586621679516288)) ((~>) [a6989586621679516287] [b6989586621679516288]) Source #
Instances
| SingI (MapMaybeSym0 :: TyFun (a ~> Maybe b) ([a] ~> [b]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Maybe Methods sing :: Sing MapMaybeSym0 Source # | |
| SuppressUnusedWarnings (MapMaybeSym0 :: TyFun (a6989586621679516287 ~> Maybe b6989586621679516288) ([a6989586621679516287] ~> [b6989586621679516288]) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Maybe Methods suppressUnusedWarnings :: () Source # | |
| type Apply (MapMaybeSym0 :: TyFun (a6989586621679516287 ~> Maybe b6989586621679516288) ([a6989586621679516287] ~> [b6989586621679516288]) -> Type) (a6989586621679516448 :: a6989586621679516287 ~> Maybe b6989586621679516288) Source # | |
Defined in Data.Singletons.Prelude.Maybe type Apply (MapMaybeSym0 :: TyFun (a6989586621679516287 ~> Maybe b6989586621679516288) ([a6989586621679516287] ~> [b6989586621679516288]) -> Type) (a6989586621679516448 :: a6989586621679516287 ~> Maybe b6989586621679516288) = MapMaybeSym1 a6989586621679516448 | |
data MapMaybeSym1 (a6989586621679516448 :: (~>) a6989586621679516287 (Maybe b6989586621679516288)) :: (~>) [a6989586621679516287] [b6989586621679516288] Source #
Instances
| SingI d => SingI (MapMaybeSym1 d :: TyFun [a] [b] -> Type) Source # | |
Defined in Data.Singletons.Prelude.Maybe Methods sing :: Sing (MapMaybeSym1 d) Source # | |
| SuppressUnusedWarnings (MapMaybeSym1 a6989586621679516448 :: TyFun [a6989586621679516287] [b6989586621679516288] -> Type) Source # | |
Defined in Data.Singletons.Prelude.Maybe Methods suppressUnusedWarnings :: () Source # | |
| type Apply (MapMaybeSym1 a6989586621679516448 :: TyFun [a] [b] -> Type) (a6989586621679516449 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.Maybe type Apply (MapMaybeSym1 a6989586621679516448 :: TyFun [a] [b] -> Type) (a6989586621679516449 :: [a]) = MapMaybe a6989586621679516448 a6989586621679516449 | |