{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeAbstractions #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UndecidableInstances #-}
module Data.String.Singletons (
  PIsString(..), SIsString(..),
  
  FromStringSym0, FromStringSym1
  ) where
import Data.Functor.Const
import Data.Functor.Const.Singletons
import Data.Functor.Identity
import Data.Functor.Identity.Singletons
import Data.Singletons.TH
import GHC.TypeLits (Symbol)
import GHC.TypeLits.Singletons ()   
$(singletonsOnly [d|
  
  
  class IsString a where
      fromString :: Symbol -> a
  
  instance IsString a => IsString (Const a (b :: k)) where
    fromString x = Const (fromString x)
  
  instance IsString a => IsString (Identity a) where
    fromString x = Identity (fromString x)
  |])
instance PIsString Symbol where
  type FromString a = a
instance SIsString Symbol where
  sFromString :: forall (t :: Symbol). Sing t -> Sing (FromString t)
sFromString Sing t
x = Sing t
Sing (FromString t)
x