named-text-1.1.2.0: A parameterized named text type and associated functionality.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Name

Description

The Name type is designed to be used in place of plain String or Text types. Fundamentally Name is an extension of Text, but it includes two type-level parameters that help to manage the underlying data: a style parameter and a nameOf parameter.

  • The style parameter is used to control various functionality and validation around the contained Text type. For example, one style is CaseInsensitive, which allows comparisons to be done independently of ASCII case.
  • The nameOf parameter is a phantom type string which ensures that two different strings aren't inadvertently swapped or combined. Any transformation from one nameOf to another nameOf must be intentional.

Example

For a more complete example, consider a login form which takes an email as the username and a password. Without the Data.Name module, the type signature might be:

   login :: String -> String -> IO Bool

There are a number of deficiencies that can be identified for this implementation, including:

  • Which argument is the email username, which is the password?
  • Is there any protection against simply printing the password to stdout?
  • Can these protections be extended to the code calling login and not just observed within the login function itself?
  • Email addresses are typically not case sensitive: does the login function provide the appropriate case handling?

Using Name, the declaration would look more like:

login :: Named CaseInsensitive "email" -> Named Secure "password" -> IO Bool

There are a number of advantages that can be observed here:

  • The arguments are self-identifying. No need to try to remember which was used for what purpose.
  • The email is treated as a case-insensitive value, both within login but also automatically in any other uses elsewhere. Setting this value automatically applies case insensitivity conversions, and comparisons are always case independent.
  • The password is secured against simply printing it or retrieving the value to use unsafely elsewhere. There is a special operation to return the actual underlying Text from a secure name, which will presumably be very carefully used only by the login implementation itself.
  • Zero runtime cost (other than where needed, such as case translation).

Alternatives:

One typical alternative approach is to use a newtype wrapper around Text or String to provide the type level safety. This is not a bad approach, but this module seeks to provide the following additional benefits over a simple newtype:

  • New names do not need a separate declaration, with associated instance declarations: simply use a new type string.
  • Names are parameterized over both style and identity, with different conversion abilities for both. Similar functionality could be established for a newtype but this would result in either a duplication of effort for each new newtype declared this way, or else a parameterization of a generic newtype in the same general manner as provided by this module (and Name *is* simply a newtype at the core).

Another approach is to use the Tagged. This module is highly similar to Tagged, but this module's Named type has two parameters and the underlying type is always Text. This module can therefore be considered a specialization of the generic capabilities of Tagged but more customized for representing textual data.

Synopsis

Core type

data Named (style :: NameStyle) (nameOf :: Symbol) Source #

The Named is a wrapper around any Text that identifies the type of Text via the nameOf phantom symbol type, as well as a usage specified by the style type parameter. Use of Named should always be preferred to using a raw Text (or String).

Instances

Instances details
Pretty (Named style nm) => Sayable tag (Named style nm) Source #

Generically the rendered version includes the textual representation of the nameOf parameter followed by the Text itself.

Instance details

Defined in Data.Name

Methods

sayable :: Named style nm -> Saying tag #

NameText style => Sayable "info" (Named style nm) Source #

For an "info" saytag (and possibly others), a Name doesn't include its label and simply shows the Text as would be rendered by "prettyprinter".

Instance details

Defined in Data.Name

Methods

sayable :: Named style nm -> Saying "info" #

FromJSON (Name nameTy) Source # 
Instance details

Defined in Data.Name.JSON

Methods

parseJSON :: Value -> Parser (Name nameTy) #

parseJSONList :: Value -> Parser [Name nameTy] #

FromJSONKey (Name nameTy) Source # 
Instance details

Defined in Data.Name.JSON

ToJSON (Name nameTy) Source # 
Instance details

Defined in Data.Name.JSON

Methods

toJSON :: Name nameTy -> Value #

toEncoding :: Name nameTy -> Encoding #

toJSONList :: [Name nameTy] -> Value #

toEncodingList :: [Name nameTy] -> Encoding #

ToJSONKey (Name nameTy) Source # 
Instance details

Defined in Data.Name.JSON

IsList (Name s) Source # 
Instance details

Defined in Data.Name

Associated Types

type Item (Name s) #

Methods

fromList :: [Item (Name s)] -> Name s #

fromListN :: Int -> [Item (Name s)] -> Name s #

toList :: Name s -> [Item (Name s)] #

FromJSON (Named CaseInsensitive nameTy) Source # 
Instance details

Defined in Data.Name.JSON

FromJSON (Named JSONStyle nameTy) Source # 
Instance details

Defined in Data.Name.JSON

FromJSONKey (Named CaseInsensitive nameTy) Source # 
Instance details

Defined in Data.Name.JSON

FromJSONKey (Named JSONStyle nameTy) Source # 
Instance details

Defined in Data.Name.JSON

ToJSON (Named CaseInsensitive nameTy) Source # 
Instance details

Defined in Data.Name.JSON

ToJSON (Named JSONStyle nameTy) Source # 
Instance details

Defined in Data.Name.JSON

ToJSONKey (Named CaseInsensitive nameTy) Source # 
Instance details

Defined in Data.Name.JSON

ToJSONKey (Named JSONStyle nameTy) Source # 
Instance details

Defined in Data.Name.JSON

IsString (Named CaseInsensitive nameOf) Source # 
Instance details

Defined in Data.Name

IsString (Named style nameOf) Source # 
Instance details

Defined in Data.Name

Methods

fromString :: String -> Named style nameOf #

Semigroup (Named style nameOf) Source # 
Instance details

Defined in Data.Name

Methods

(<>) :: Named style nameOf -> Named style nameOf -> Named style nameOf #

sconcat :: NonEmpty (Named style nameOf) -> Named style nameOf #

stimes :: Integral b => b -> Named style nameOf -> Named style nameOf #

Generic (Named style nameOf) Source # 
Instance details

Defined in Data.Name

Associated Types

type Rep (Named style nameOf) :: Type -> Type #

Methods

from :: Named style nameOf -> Rep (Named style nameOf) x #

to :: Rep (Named style nameOf) x -> Named style nameOf #

Sayable "show" (Named style nm) => Show (Named style nm) Source #

There is also a Show method; this is *not* the inverse of a Read, and in fact there is no Read instance for Named. The Sayable instance is preferred over Show, but Show is provided for default considerations such as test failure reporting.

Instance details

Defined in Data.Name

Methods

showsPrec :: Int -> Named style nm -> ShowS #

show :: Named style nm -> String #

showList :: [Named style nm] -> ShowS #

NFData (Named style nameOf) Source # 
Instance details

Defined in Data.Name

Methods

rnf :: Named style nameOf -> () #

Eq (Named style nameOf) Source # 
Instance details

Defined in Data.Name

Methods

(==) :: Named style nameOf -> Named style nameOf -> Bool #

(/=) :: Named style nameOf -> Named style nameOf -> Bool #

Ord (Named style nameOf) Source # 
Instance details

Defined in Data.Name

Methods

compare :: Named style nameOf -> Named style nameOf -> Ordering #

(<) :: Named style nameOf -> Named style nameOf -> Bool #

(<=) :: Named style nameOf -> Named style nameOf -> Bool #

(>) :: Named style nameOf -> Named style nameOf -> Bool #

(>=) :: Named style nameOf -> Named style nameOf -> Bool #

max :: Named style nameOf -> Named style nameOf -> Named style nameOf #

min :: Named style nameOf -> Named style nameOf -> Named style nameOf #

Hashable (Named style nameOf) Source # 
Instance details

Defined in Data.Name

Methods

hashWithSalt :: Int -> Named style nameOf -> Int #

hash :: Named style nameOf -> Int #

IsText (Named CaseInsensitive nameOf) Source # 
Instance details

Defined in Data.Name

IsText (Named style nameOf) Source # 
Instance details

Defined in Data.Name

Methods

fromText :: Text -> Named style nameOf Source #

KnownSymbol ty => Pretty (Named CaseInsensitive ty) Source # 
Instance details

Defined in Data.Name

Methods

pretty :: Named CaseInsensitive ty -> Doc ann #

prettyList :: [Named CaseInsensitive ty] -> Doc ann #

(KnownSymbol ty, NameText style) => Pretty (Named style ty) Source #

This is the general pretty rendering for a Named object. This can be overriden for specific types or styles for a different rendering.

Instance details

Defined in Data.Name

Methods

pretty :: Named style ty -> Doc ann #

prettyList :: [Named style ty] -> Doc ann #

type Item (Name s) Source # 
Instance details

Defined in Data.Name

type Item (Name s) = Item Text
type Rep (Named style nameOf) Source # 
Instance details

Defined in Data.Name

type Rep (Named style nameOf) = D1 ('MetaData "Named" "Data.Name" "named-text-1.1.2.0-B6yNp06lBZx1X1LRqX7XoJ" 'True) (C1 ('MetaCons "Named" 'PrefixI 'True) (S1 ('MetaSel ('Just "named") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

nameOf :: KnownSymbol nameOf => Named style nameOf -> Proxy# nameOf -> String Source #

Retrieve the nameOf type parameter (the "what am I") of a Named as a text value

nameProxy :: KnownSymbol nameOf => Named style nameOf -> Proxy nameOf Source #

Retrieve a proxy for the nameOf parameter of Named.

styleProxy :: KnownSymbol style => Named style nameOf -> Proxy style Source #

Retrieve a proxy for the style parameter of Named.

data SomeName Source #

The SomeName data type is used to existentially hide the identification type parameter for Named objects. This is usually used when names of different types are mixed together in some container or other name-agnostic interface.

Constructors

forall (s :: Symbol).KnownSymbol s => SomeName (Name s) 

viewSomeName :: (forall (s :: Symbol). KnownSymbol s => Name s -> r) -> SomeName -> r Source #

The viewSomeName function is used to project the Named object with its identification type parameter existentially recovered to a function that will consume that Named object and return some sort of result.

class HasName x style nm | x -> style, x -> nm Source #

Some objects have (contain) an associated name that identifies or labels that object. If they do, they can declare the HasName constraint, and use its myName method to reconstitute the Named from the object.

Minimal complete definition

myName

myName :: HasName x style nm => x -> Named style nm Source #

myName can be used to extract the associated Named from an object.

Style management

Defines the style type parameter and some well-known styles directly supported by this module. Users may define additional styles as needed.

type NameStyle = Symbol Source #

The NameStyle specifies how the name itself is styled.

  • The UTF8 default style is orthogonal to a normal String or Text.
  • The CaseInsensitive style indicates that uppercase ASCII characters are equivalent to their lowercase form.
  • The Secure style is case sensitive, but does not reveal the full contents unless the specific "secureName" accessor function is used. This is useful for storing secrets (e.g. passphrases, access tokens, etc.) that should not be fully visible in log messages and other miscellaneous output.

These styles will be described in more detail below.

data SomeNameStyle nameTy Source #

The SomeNameStyle data type is used to existentially hide the style type of Named objects. This is usually used when names of different styles are mixed together in some container or other style-agnostic interface.

Constructors

forall (s :: Symbol).(KnownSymbol s, NameText s) => SomeNameStyle (Named s nameTy) 

viewSomeNameStyle :: (forall (s :: Symbol). (KnownSymbol s, NameText s) => Named s nameTy -> r) -> SomeNameStyle nameTy -> r Source #

The viewSomeNameStyle function is used to project the Named object with its style type existentially recovered to a function that will consume that Named object and return some sort of result.

Creating a Name

The Named type is an instance of IsString, so a name can be created from a string via fromString. In addition, this module defines an IsText class with a fromText method that operates in a parallel fashion.

class IsText a where Source #

The IsText class provides similar functionality to the IsString class, but with Text sources instead of String sources. Defining an instance of this class allows the use of fromText to convert from Text to the target type (which does not necessarily need to be a Named type, and this generic class should be deprecated in favor of a generic implementation the the "text" library).

Methods

fromText :: Text -> a Source #

Instances

Instances details
IsText (Named CaseInsensitive nameOf) Source # 
Instance details

Defined in Data.Name

IsText (Named style nameOf) Source # 
Instance details

Defined in Data.Name

Methods

fromText :: Text -> Named style nameOf Source #

Conversions

class NameText style => ConvertName style origTy newTy where Source #

Conversion from a Named with one nameOf to a separate nameOf must be done explicitly; the recommended method is via an instance of the ConvertName class, which provides the convertName method to perform the requested conversion. If there should not be a conversion between the two Named types, no ConvertName class should be defined, and users should refrain from providing an alternative explicit function to perform this conversion.

Minimal complete definition

Nothing

Methods

convertName :: Named style origTy -> Named style newTy Source #

Instances

Instances details
ConvertName UTF8 a a Source # 
Instance details

Defined in Data.Name

class (NameText inpStyle, IsText (Named outStyle nameTy)) => ConvertNameStyle inpStyle outStyle nameTy where Source #

A Named can be converted from one style to another with an instance of the ConvertNameStyle class. If no conversion should be supported, no instance should be defined. Users are highly recommended to use the convertStyle method (instead of a separate manual conversion function) to ensure proper conversions are performed.

Minimal complete definition

Nothing

Methods

convertStyle :: Named inpStyle nameTy -> Named outStyle nameTy Source #

Instances

Instances details
ConvertNameStyle CaseInsensitive JSONStyle nameOf Source # 
Instance details

Defined in Data.Name.JSON

ConvertNameStyle UTF8 JSONStyle nameOf Source # 
Instance details

Defined in Data.Name.JSON

Methods

convertStyle :: Named UTF8 nameOf -> Named JSONStyle nameOf Source #

ConvertNameStyle JSONStyle CaseInsensitive nameOf Source # 
Instance details

Defined in Data.Name.JSON

ConvertNameStyle JSONStyle UTF8 nameOf Source # 
Instance details

Defined in Data.Name.JSON

Methods

convertStyle :: Named JSONStyle nameOf -> Named UTF8 nameOf Source #

Extraction and rendering

For rendering, the sayable package is preferred (as provided by the Sayable instances, which is an extension of the "prettyprinter" package (and users desiring a "prettyprinter" output can extract that from the sayable representation).

class NameText style Source #

A general class that can be used to extract the Text back out of a name. This should be the preferred method of obtaining the raw Text, and should be used carefully as all of the protections provided by this module are no longer available for that raw Text. In addition, no instance of this class is provided where the name should not be extractable, and this method may extract a modified form of the text (e.g. the Secure namestyle will return a masked version of the original Text).

Instances

Instances details
NameText CaseInsensitive Source # 
Instance details

Defined in Data.Name

Methods

nameText :: forall (nm :: Symbol). Named CaseInsensitive nm -> Text Source #

NameText Secure Source # 
Instance details

Defined in Data.Name

Methods

nameText :: forall (nm :: Symbol). Named Secure nm -> Text Source #

NameText UTF8 Source # 
Instance details

Defined in Data.Name

Methods

nameText :: forall (nm :: Symbol). Named UTF8 nm -> Text Source #

NameText JSONStyle Source # 
Instance details

Defined in Data.Name.JSON

Methods

nameText :: forall (nm :: Symbol). Named JSONStyle nm -> Text Source #

nameText :: NameText style => Named style nm -> Text Source #

nameText is used to retrieve the original Text text from a Named object of the specified style. This should be the main method used to extract the Text from a Named, but it should be used carefully because the protections offered by the Named type will no longer be available for the raw Text.

Regular (UTF-8) Names

type UTF8 = "UTF8" :: NameStyle Source #

The UTF8 type alias is useable as the style parameter of a Named type. The type-string form may also be used but the type alias is designed to allow abstraction from the raw type-string value.

type Name = Named UTF8 Source #

The Name type is for the standard/most commonly used style which is orthogonal to a normal String or Text. Because this is the most frequently used form of Named, it has a type alias to shorten the usage references.

name :: Name nameOf -> Text Source #

Deprecated: Use nameText instead

Case Insensitive Names

type CaseInsensitive = "CaseInsensitive" :: NameStyle Source #

The CaseInsensitive style of Named objects will allow case-insensitive ASCII comparisons between objects. On creation, all text is converted to lowercase, so the original input case is not preserved on extraction or rendering.

caselessName :: Named CaseInsensitive nameOf -> Text Source #

Deprecated: Use nameText instead

Secure Names

type Secure = "SECURE!" :: NameStyle Source #

The Secure style of Named objects masks the internal text on extraction or rendering to avoid leaking information. The actual internal text can be retrieved only with the explicit secureNameBypass function.

type SecureName = Named Secure Source #

The SecureName is like Name, but its display form does not reveal the full name. The use of the nameText extractor or any of the renderers will occlude a portion of the secure name to avoid revealing it in its entirety.

secureName :: Named Secure nameOf -> Text Source #

Deprecated: Use nameText instead

The secureName accessor is used to obtain the name field from a Secure Named. This is the normal accessor for a Secure Named and will occlude a portion of the extracted name for protection. For those specific cases where the full Secure Named text is needed, the secureNameBypass accessor should be used instead.

secureNameBypass :: Named Secure nameOf -> Text Source #

The secureNameBypass accessor is used to obtain the raw Text from a Secure Named; this essentially BYPASSES THE SECURITY PROTECTION and should only be used in the limited cases when the raw form is absolutely needed.

Constraining allowed names

class (KnownNat (AllowedNameType nameOf ntl), DisallowedNameType nameOf ntl ntl) => ValidNames (nameOf :: Symbol) (ntl :: [Symbol]) Source #

The ValidNames constraint can be used to specify the list of allowed names for a parameterized name argument. For example:

foo :: ValidNames n '[ "right", "correct" ] => Name n -> a

The above allows foo to be called with a Name "right" or a Name "correct", but if it is called with any other Named nameOf parameter then a compilation error will be generated indicating "the supplied nameOf type parameter is not in the allowed Names".

All instances of this class are pre-defined by this module and the user should not need to create any instances.

Minimal complete definition

validName

Instances

Instances details
(KnownNat (AllowedNameType nty ntl), DisallowedNameType nty ntl ntl) => ValidNames nty ntl Source # 
Instance details

Defined in Data.Name

Methods

validName :: Proxy ntl -> Name nty -> Text Source #

validName :: ValidNames nameOf ntl => Proxy ntl -> Name nameOf -> Text Source #

The validName method is used to extract the text form of a Name for which nameOf is a member of the valid names specified by the ntl type list. It corresponds to nameText while also providing the validation of the extraction.

Utility operations

nameLength :: Named style nm -> Natural Source #

Returns the length of the underlying Text

nullName :: Named style nm -> Bool Source #

Returns true if the name value is empty.