mmzk-typeid-0.6.3.1: A TypeID and UUIDv7 implementation for Haskell
LicenseMIT
Maintainermmzk1526@outlook.com
PortabilityGHC
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.KindID.Class

Description

This module contains the type-level mechanisms that are used to define custom KindID-ish identifier types.

Synopsis

Prefix

type ValidPrefix prefix = (KnownSymbol prefix, LengthLT64C prefix, IsLUSymbolC prefix) Source #

A constraint for valid prefix Symbols.

class ToPrefix a Source #

A class that translates any kind to a Symbol. It is used to translate custom data kinds to a Symbol so that they can be used as KindID prefixes.

For example, suppose we have the following data structure that represents the prefixes we are going to use:

data Prefix = User | Post | Comment | SuperUser

Then we can make it an instance of ToPrefix like this:

instance ToPrefix 'User where
  type PrefixSymbol 'User = "user"

instance ToPrefix 'Post where
  type PrefixSymbol 'Post = "post"

instance ToPrefix 'Comment where
  type PrefixSymbol 'Comment = "comment"

instance ToPrefix 'SuperUser where
  type PrefixSymbol 'SuperUser = "super_user"

Now we can use Prefix as a prefix for KindIDs, e.g.

do
  userID    <- genKindID @'User      -- Same as genKindID @"user"
  postID    <- genKindID @'Post      -- Same as genKindID @"post"
  commentID <- genKindID @'Comment   -- Same as genKindID @"comment"
  suID      <- genKindID @'SuperUser -- Same as genKindID @"super_user"

Associated Types

type PrefixSymbol a :: Symbol Source #

Instances

Instances details
ToPrefix (s :: Symbol) Source #

The PrefixSymbol of a Symbol is the Symbol itself.

Instance details

Defined in Data.KindID.Class

Associated Types

type PrefixSymbol s :: Symbol Source #

Helpers

type family LengthLT64C (prefix :: Symbol) :: Constraint where ... Source #

Contains a custom error message if the prefix Symbol is too long.

Equations

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 ... Source #

Contains a custom error message if the prefix Symbol is not lowercase + underscore or it starts or ends with underscores.

Equations

IsLUSymbolC s = If (IsLUSymbol s) (() :: Constraint) (TypeError ((Text "The prefix " :<>: ShowType s) :<>: Text " is not valid!")) 

type family LengthSymbol (prefix :: Symbol) :: Nat where ... Source #

The length of a Symbol as a Nat.

Equations

LengthSymbol prefix = LSUH (UnconsSymbol prefix) 

type family IsLowerChar (ch :: Char) :: Bool where ... Source #

Is a type-level Char lowercase?

Equations

IsLowerChar ch = (Compare '`' ch == 'LT) && (Compare ch '{' == 'LT) 

type family IsUnderscore (ch :: Char) :: Bool where ... Source #

Is a type-level Char an underscore?

Equations

IsUnderscore ch = Compare '_' ch == 'EQ 

type family IsLUSymbol (prefix :: Symbol) :: Bool where ... Source #

Is a Symbol lowercase + underscore and not start or end with underscores?

Equations

IsLUSymbol prefix = ILUSUH1 (UnconsSymbol prefix) 

type family ILUSUH1 (uncons :: Maybe (Char, Symbol)) :: Bool where ... Source #

First IsLUSymbol Uncons Helper.

Equations

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 ... Source #

Second IsLUSymbol Uncons Helper.

Equations

ILUSUH2 'Nothing = True 
ILUSUH2 ('Just '(c, "")) = IsLowerChar c 
ILUSUH2 ('Just '(c, s)) = (IsLowerChar c || IsUnderscore c) && ILUSUH2 (UnconsSymbol s) 

Deprecated Helpers

type family IsLowerSymbol (prefix :: Symbol) :: Bool where ... Source #

Deprecated: No longer used; to be removed in version 0.7

Is a Symbol lowercase?

Equations

IsLowerSymbol prefix = ILSUH (UnconsSymbol prefix) 

type family LSUH (uncons :: Maybe (Char, Symbol)) :: Nat where ... Source #

LengthSymbol Uncons Helper.

Equations

LSUH 'Nothing = 0 
LSUH ('Just '(c, s)) = 1 + LengthSymbol s 

type family ILSUH (uncons :: Maybe (Char, Symbol)) :: Bool where ... Source #

Deprecated: No longer used; to be removed in the version 0.7

Is LowerSymbol Uncons Helper.

Equations

ILSUH 'Nothing = 'True 
ILSUH ('Just '(c, s)) = IsLowerChar c && IsLowerSymbol s