Copyright | (C) 2017 Ryan Scott |
---|---|
License | BSD-style (see LICENSE) |
Maintainer | Ryan Scott |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
Defines and exports a promoted and singled version of the IsString
type class from Data.String.
Synopsis
- class PIsString (a :: Type) where
- type FromString (arg :: Symbol) :: a
- class SIsString a where
- sFromString :: forall (t :: Symbol). Sing t -> Sing (Apply FromStringSym0 t :: a)
- data FromStringSym0 :: forall a6989586621681182111. (~>) Symbol a6989586621681182111
- type FromStringSym1 (arg6989586621681182147 :: Symbol) = FromString arg6989586621681182147
Documentation
class PIsString (a :: Type) Source #
type FromString (arg :: Symbol) :: a Source #
Instances
PIsString Symbol Source # | |
Defined in Data.Singletons.Prelude.IsString type FromString arg :: a Source # | |
PIsString (Identity a) Source # | |
Defined in Data.Singletons.Prelude.IsString type FromString arg :: a Source # | |
PIsString (Const a b) Source # | |
Defined in Data.Singletons.Prelude.IsString type FromString arg :: a Source # |
class SIsString a where Source #
sFromString :: forall (t :: Symbol). Sing t -> Sing (Apply FromStringSym0 t :: a) Source #
Instances
SIsString Symbol Source # | |
Defined in Data.Singletons.Prelude.IsString sFromString :: Sing t -> Sing (Apply FromStringSym0 t) Source # | |
SIsString a => SIsString (Identity a) Source # | |
Defined in Data.Singletons.Prelude.IsString sFromString :: Sing t -> Sing (Apply FromStringSym0 t) Source # | |
SIsString a => SIsString (Const a b) Source # | |
Defined in Data.Singletons.Prelude.IsString sFromString :: Sing t -> Sing (Apply FromStringSym0 t) Source # |
Defunctionalization symbols
data FromStringSym0 :: forall a6989586621681182111. (~>) Symbol a6989586621681182111 Source #
Instances
SIsString a => SingI (FromStringSym0 :: TyFun Symbol a -> Type) Source # | |
Defined in Data.Singletons.Prelude.IsString | |
SuppressUnusedWarnings (FromStringSym0 :: TyFun Symbol a6989586621681182111 -> Type) Source # | |
Defined in Data.Singletons.Prelude.IsString suppressUnusedWarnings :: () Source # | |
type Apply (FromStringSym0 :: TyFun Symbol k2 -> Type) (arg6989586621681182147 :: Symbol) Source # | |
Defined in Data.Singletons.Prelude.IsString type Apply (FromStringSym0 :: TyFun Symbol k2 -> Type) (arg6989586621681182147 :: Symbol) = (FromString arg6989586621681182147 :: k2) |
type FromStringSym1 (arg6989586621681182147 :: Symbol) = FromString arg6989586621681182147 Source #