{-# LANGUAGE UndecidableInstances #-}
module Data.KindID.Class
(
ValidPrefix
, ToPrefix(..)
, LengthLT64C
, IsLUSymbolC
, LengthSymbol
, IsLowerChar
, IsUnderscore
, IsLUSymbol
, ILUSUH1
, ILUSUH2
, IsLowerSymbol
, LSUH
, ILSUH
) where
import Data.Kind
import Data.Type.Bool
import Data.Type.Equality
import Data.Type.Ord
import GHC.TypeLits
class ToPrefix a where
type PrefixSymbol a :: Symbol
instance ToPrefix (s :: Symbol) where
type PrefixSymbol s = s
type ValidPrefix prefix = ( KnownSymbol prefix
, LengthLT64C prefix
, IsLUSymbolC prefix )
type family LengthLT64C (prefix :: Symbol) :: Constraint where
LengthLT64C s
= If (Compare (LengthSymbol s) 64 == 'LT) (() :: Constraint)
( TypeError ( Text "The prefix "
:<>: ShowType s
:<>: Text " with "
:<>: ShowType (LengthSymbol s)
:<>: Text " characters is too long!" ) )
type family IsLUSymbolC (prefix :: Symbol) :: Constraint where
IsLUSymbolC s
= If (IsLUSymbol s) (() :: Constraint)
( TypeError ( Text "The prefix "
:<>: ShowType s
:<>: Text " is not valid!" ) )
type family LengthSymbol (prefix :: Symbol) :: Nat where
LengthSymbol prefix = LSUH (UnconsSymbol prefix)
type family LSUH (uncons :: Maybe (Char, Symbol)) :: Nat where
LSUH 'Nothing = 0
LSUH ('Just '( c, s )) = 1 + LengthSymbol s
type family IsLowerChar (ch :: Char) :: Bool where
IsLowerChar ch = Compare '`' ch == 'LT && Compare ch '{' == 'LT
type family IsUnderscore (ch :: Char) :: Bool where
IsUnderscore ch = Compare '_' ch == 'EQ
type family IsLUSymbol (prefix :: Symbol) :: Bool where
IsLUSymbol prefix = ILUSUH1 (UnconsSymbol prefix)
type family ILUSUH1 (uncons :: Maybe (Char, Symbol)) :: Bool where
ILUSUH1 'Nothing = True
ILUSUH1 ('Just '( '_', _ )) = False
ILUSUH1 ('Just '( c, s )) = (IsLowerChar c || IsUnderscore c)
&& ILUSUH2 (UnconsSymbol s)
type family ILUSUH2 (uncons :: Maybe (Char, Symbol)) :: Bool where
ILUSUH2 'Nothing = True
ILUSUH2 ('Just '( c, "" )) = IsLowerChar c
ILUSUH2 ('Just '( c, s )) = (IsLowerChar c || IsUnderscore c)
&& ILUSUH2 (UnconsSymbol s)
type family IsLowerSymbol (prefix :: Symbol) :: Bool where
IsLowerSymbol prefix = ILSUH (UnconsSymbol prefix)
{-# DEPRECATED IsLowerSymbol "No longer used; to be removed in version 0.7" #-}
type family ILSUH (uncons :: Maybe (Char, Symbol)) :: Bool where
ILSUH 'Nothing = 'True
ILSUH ('Just '( c, s )) = IsLowerChar c && IsLowerSymbol s
{-# DEPRECATED ILSUH "No longer used; to be removed in the version 0.7" #-}