{-# LANGUAGE CPP #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE ExplicitNamespaces #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
module Data.Name
(
Named
, nameOf
, nameProxy
, styleProxy
, SomeName(SomeName), viewSomeName
, HasName, myName
, NameStyle
, SomeNameStyle(SomeNameStyle), viewSomeNameStyle
, IsText(fromText)
, ConvertName(convertName)
, ConvertNameStyle(convertStyle)
, NameText, nameText
, UTF8
, type Name
, name
, CaseInsensitive
, caselessName
, Secure
, SecureName, secureName, secureNameBypass
, ValidNames, validName
, nameLength
, nullName
)
where
import Control.DeepSeq ( NFData )
import Data.Hashable ( Hashable )
import Data.Proxy ( Proxy(Proxy) )
import Data.String ( IsString(fromString) )
import Data.Text ( Text )
import qualified Data.Text as T
import GHC.Exts ( Proxy#, proxy#, IsList(fromList, toList), Item )
import GHC.Generics ( Generic )
import GHC.TypeLits
import Prettyprinter ( (<+>) )
import qualified Prettyprinter as PP
import Text.Sayable
#if !MIN_VERSION_base(4,16,0)
import Numeric.Natural
#endif
newtype Named (style :: NameStyle) (nameOf :: Symbol) = Named { forall (style :: Symbol) (nameOf :: Symbol).
Named style nameOf -> Text
named :: Text }
deriving (Named style nameOf -> Named style nameOf -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall (style :: Symbol) (nameOf :: Symbol).
Named style nameOf -> Named style nameOf -> Bool
/= :: Named style nameOf -> Named style nameOf -> Bool
$c/= :: forall (style :: Symbol) (nameOf :: Symbol).
Named style nameOf -> Named style nameOf -> Bool
== :: Named style nameOf -> Named style nameOf -> Bool
$c== :: forall (style :: Symbol) (nameOf :: Symbol).
Named style nameOf -> Named style nameOf -> Bool
Eq, Named style nameOf -> Named style nameOf -> Bool
Named style nameOf -> Named style nameOf -> Ordering
Named style nameOf -> Named style nameOf -> Named style nameOf
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall (style :: Symbol) (nameOf :: Symbol).
Eq (Named style nameOf)
forall (style :: Symbol) (nameOf :: Symbol).
Named style nameOf -> Named style nameOf -> Bool
forall (style :: Symbol) (nameOf :: Symbol).
Named style nameOf -> Named style nameOf -> Ordering
forall (style :: Symbol) (nameOf :: Symbol).
Named style nameOf -> Named style nameOf -> Named style nameOf
min :: Named style nameOf -> Named style nameOf -> Named style nameOf
$cmin :: forall (style :: Symbol) (nameOf :: Symbol).
Named style nameOf -> Named style nameOf -> Named style nameOf
max :: Named style nameOf -> Named style nameOf -> Named style nameOf
$cmax :: forall (style :: Symbol) (nameOf :: Symbol).
Named style nameOf -> Named style nameOf -> Named style nameOf
>= :: Named style nameOf -> Named style nameOf -> Bool
$c>= :: forall (style :: Symbol) (nameOf :: Symbol).
Named style nameOf -> Named style nameOf -> Bool
> :: Named style nameOf -> Named style nameOf -> Bool
$c> :: forall (style :: Symbol) (nameOf :: Symbol).
Named style nameOf -> Named style nameOf -> Bool
<= :: Named style nameOf -> Named style nameOf -> Bool
$c<= :: forall (style :: Symbol) (nameOf :: Symbol).
Named style nameOf -> Named style nameOf -> Bool
< :: Named style nameOf -> Named style nameOf -> Bool
$c< :: forall (style :: Symbol) (nameOf :: Symbol).
Named style nameOf -> Named style nameOf -> Bool
compare :: Named style nameOf -> Named style nameOf -> Ordering
$ccompare :: forall (style :: Symbol) (nameOf :: Symbol).
Named style nameOf -> Named style nameOf -> Ordering
Ord, forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (style :: Symbol) (nameOf :: Symbol) x.
Rep (Named style nameOf) x -> Named style nameOf
forall (style :: Symbol) (nameOf :: Symbol) x.
Named style nameOf -> Rep (Named style nameOf) x
$cto :: forall (style :: Symbol) (nameOf :: Symbol) x.
Rep (Named style nameOf) x -> Named style nameOf
$cfrom :: forall (style :: Symbol) (nameOf :: Symbol) x.
Named style nameOf -> Rep (Named style nameOf) x
Generic, Named style nameOf -> ()
forall a. (a -> ()) -> NFData a
forall (style :: Symbol) (nameOf :: Symbol).
Named style nameOf -> ()
rnf :: Named style nameOf -> ()
$crnf :: forall (style :: Symbol) (nameOf :: Symbol).
Named style nameOf -> ()
NFData, NonEmpty (Named style nameOf) -> Named style nameOf
Named style nameOf -> Named style nameOf -> Named style nameOf
forall b.
Integral b =>
b -> Named style nameOf -> Named style nameOf
forall a.
(a -> a -> a)
-> (NonEmpty a -> a)
-> (forall b. Integral b => b -> a -> a)
-> Semigroup a
forall (style :: Symbol) (nameOf :: Symbol).
NonEmpty (Named style nameOf) -> Named style nameOf
forall (style :: Symbol) (nameOf :: Symbol).
Named style nameOf -> Named style nameOf -> Named style nameOf
forall (style :: Symbol) (nameOf :: Symbol) b.
Integral b =>
b -> Named style nameOf -> Named style nameOf
stimes :: forall b.
Integral b =>
b -> Named style nameOf -> Named style nameOf
$cstimes :: forall (style :: Symbol) (nameOf :: Symbol) b.
Integral b =>
b -> Named style nameOf -> Named style nameOf
sconcat :: NonEmpty (Named style nameOf) -> Named style nameOf
$csconcat :: forall (style :: Symbol) (nameOf :: Symbol).
NonEmpty (Named style nameOf) -> Named style nameOf
<> :: Named style nameOf -> Named style nameOf -> Named style nameOf
$c<> :: forall (style :: Symbol) (nameOf :: Symbol).
Named style nameOf -> Named style nameOf -> Named style nameOf
Semigroup)
type NameStyle = Symbol
instance Hashable (Named style nameOf)
nameOf :: KnownSymbol nameOf => Named style nameOf -> Proxy# nameOf -> String
nameOf :: forall (nameOf :: Symbol) (style :: Symbol).
KnownSymbol nameOf =>
Named style nameOf -> Proxy# nameOf -> String
nameOf Named style nameOf
_ = forall (n :: Symbol). KnownSymbol n => Proxy# n -> String
symbolVal'
nameProxy :: KnownSymbol nameOf => Named style nameOf -> Proxy nameOf
nameProxy :: forall (nameOf :: Symbol) (style :: Symbol).
KnownSymbol nameOf =>
Named style nameOf -> Proxy nameOf
nameProxy Named style nameOf
_ = forall {k} (t :: k). Proxy t
Proxy
styleProxy :: KnownSymbol style => Named style nameOf -> Proxy style
styleProxy :: forall (style :: Symbol) (nameOf :: Symbol).
KnownSymbol style =>
Named style nameOf -> Proxy style
styleProxy Named style nameOf
_ = forall {k} (t :: k). Proxy t
Proxy
instance {-# OVERLAPPABLE #-} IsString (Named style nameOf) where
fromString :: String -> Named style nameOf
fromString = forall (style :: Symbol) (nameOf :: Symbol).
Text -> Named style nameOf
Named forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. IsString a => String -> a
fromString
class IsText a where fromText :: Text -> a
instance {-# OVERLAPPABLE #-} IsText (Named style nameOf) where
fromText :: Text -> Named style nameOf
fromText = forall (style :: Symbol) (nameOf :: Symbol).
Text -> Named style nameOf
Named
class NameText style => ConvertName style origTy newTy where
convertName :: Named style origTy -> Named style newTy
convertName = forall a. IsText a => Text -> a
fromText forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (style :: Symbol) (nm :: Symbol).
NameText style =>
Named style nm -> Text
nameText
class ( NameText inpStyle
, IsText (Named outStyle nameTy)
)
=> ConvertNameStyle inpStyle outStyle nameTy where
convertStyle :: Named inpStyle nameTy -> Named outStyle nameTy
convertStyle = forall a. IsText a => Text -> a
fromText forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (style :: Symbol) (nm :: Symbol).
NameText style =>
Named style nm -> Text
nameText
class NameText style where
nameText :: Named style nm -> Text
nameText = forall (style :: Symbol) (nameOf :: Symbol).
Named style nameOf -> Text
named
class HasName x style nm | x -> style, x -> nm where
myName :: x -> Named style nm
instance NameText style => Sayable "info" (Named style nm) where
sayable :: Named style nm -> Saying "info"
sayable = forall (tag :: Symbol). Doc SayableAnn -> Saying tag
Saying forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a ann. Pretty a => a -> Doc ann
PP.pretty forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (style :: Symbol) (nm :: Symbol).
NameText style =>
Named style nm -> Text
nameText
instance {-# OVERLAPPABLE #-} (PP.Pretty (Named style nm)
) => Sayable tag (Named style nm)
where sayable :: Named style nm -> Saying tag
sayable = forall (tag :: Symbol). Doc SayableAnn -> Saying tag
Saying forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a ann. Pretty a => a -> Doc ann
PP.pretty
instance (Sayable "show" (Named style nm)) => Show (Named style nm) where
show :: Named style nm -> String
show = forall (saytag :: Symbol) a. Sayable saytag a => a -> String
sez @"show"
instance {-# OVERLAPPABLE #-} ( KnownSymbol ty
, NameText style
)
=> PP.Pretty (Named style ty) where
pretty :: forall ann. Named style ty -> Doc ann
pretty Named style ty
nm = (forall a ann. Pretty a => a -> Doc ann
PP.pretty forall a b. (a -> b) -> a -> b
$ forall (nameOf :: Symbol) (style :: Symbol).
KnownSymbol nameOf =>
Named style nameOf -> Proxy# nameOf -> String
nameOf Named style ty
nm forall {k} (a :: k). Proxy# a
proxy#)
forall ann. Doc ann -> Doc ann -> Doc ann
<+> forall ann. Doc ann -> Doc ann
PP.squotes (forall a ann. Pretty a => a -> Doc ann
PP.pretty (forall (style :: Symbol) (nm :: Symbol).
NameText style =>
Named style nm -> Text
nameText Named style ty
nm))
nameLength :: Named style nm -> Natural
nameLength :: forall (style :: Symbol) (nm :: Symbol). Named style nm -> Natural
nameLength = forall a. Enum a => Int -> a
toEnum forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Int
T.length forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (style :: Symbol) (nameOf :: Symbol).
Named style nameOf -> Text
named
nullName :: Named style nm -> Bool
nullName :: forall (style :: Symbol) (nm :: Symbol). Named style nm -> Bool
nullName = Text -> Bool
T.null forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (style :: Symbol) (nameOf :: Symbol).
Named style nameOf -> Text
named
data SomeName =
forall (s :: Symbol) . KnownSymbol s => SomeName (Name s)
viewSomeName :: (forall (s :: Symbol) . KnownSymbol s => Name s -> r) -> SomeName -> r
viewSomeName :: forall r.
(forall (s :: Symbol). KnownSymbol s => Name s -> r)
-> SomeName -> r
viewSomeName forall (s :: Symbol). KnownSymbol s => Name s -> r
f (SomeName Name s
n) = forall (s :: Symbol). KnownSymbol s => Name s -> r
f Name s
n
data SomeNameStyle nameTy =
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
viewSomeNameStyle :: forall (nameTy :: Symbol) r.
(forall (s :: Symbol).
(KnownSymbol s, NameText s) =>
Named s nameTy -> r)
-> SomeNameStyle nameTy -> r
viewSomeNameStyle forall (s :: Symbol).
(KnownSymbol s, NameText s) =>
Named s nameTy -> r
f (SomeNameStyle Named s nameTy
n) = forall (s :: Symbol).
(KnownSymbol s, NameText s) =>
Named s nameTy -> r
f Named s nameTy
n
type UTF8 = "UTF8" :: NameStyle
type Name = Named UTF8
{-# DEPRECATED name "Use nameText instead" #-}
name :: Name nameOf -> Text
name :: forall (nameOf :: Symbol). Name nameOf -> Text
name = forall (style :: Symbol) (nm :: Symbol).
NameText style =>
Named style nm -> Text
nameText
instance IsList (Name s) where
type Item (Name s) = Item Text
fromList :: [Item (Name s)] -> Name s
fromList = forall a. IsText a => Text -> a
fromText forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall l. IsList l => [Item l] -> l
fromList
toList :: Name s -> [Item (Name s)]
toList = forall l. IsList l => l -> [Item l]
toList forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (style :: Symbol) (nm :: Symbol).
NameText style =>
Named style nm -> Text
nameText
instance ConvertName UTF8 a a where convertName :: Named UTF8 a -> Named UTF8 a
convertName = forall a. a -> a
id
instance NameText UTF8
type CaseInsensitive = "CaseInsensitive" :: NameStyle
instance {-# OVERLAPPING #-} IsString (Named CaseInsensitive nameOf) where
fromString :: String -> Named CaseInsensitive nameOf
fromString = forall (style :: Symbol) (nameOf :: Symbol).
Text -> Named style nameOf
Named forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
T.toLower forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. IsString a => String -> a
fromString
instance {-# OVERLAPPING #-} IsText (Named CaseInsensitive nameOf) where
fromText :: Text -> Named CaseInsensitive nameOf
fromText = forall (style :: Symbol) (nameOf :: Symbol).
Text -> Named style nameOf
Named forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
T.toLower
instance KnownSymbol ty => PP.Pretty (Named CaseInsensitive ty) where
pretty :: forall ann. Named CaseInsensitive ty -> Doc ann
pretty Named CaseInsensitive ty
nm = (forall a ann. Pretty a => a -> Doc ann
PP.pretty forall a b. (a -> b) -> a -> b
$ forall (nameOf :: Symbol) (style :: Symbol).
KnownSymbol nameOf =>
Named style nameOf -> Proxy# nameOf -> String
nameOf Named CaseInsensitive ty
nm forall {k} (a :: k). Proxy# a
proxy#)
forall ann. Doc ann -> Doc ann -> Doc ann
<+> forall ann. Doc ann -> Doc ann -> Doc ann -> Doc ann
PP.surround (forall a ann. Pretty a => a -> Doc ann
PP.pretty (forall (nameOf :: Symbol). Named CaseInsensitive nameOf -> Text
caselessName Named CaseInsensitive ty
nm)) Doc ann
"«" Doc ann
"»"
instance NameText CaseInsensitive
{-# DEPRECATED caselessName "Use nameText instead" #-}
caselessName :: Named CaseInsensitive nameOf -> Text
caselessName :: forall (nameOf :: Symbol). Named CaseInsensitive nameOf -> Text
caselessName = forall (style :: Symbol) (nm :: Symbol).
NameText style =>
Named style nm -> Text
nameText
type Secure = "SECURE!" :: NameStyle
type SecureName = Named Secure
{-# DEPRECATED secureName "Use nameText instead" #-}
secureName :: Named Secure nameOf -> Text
secureName :: forall (nameOf :: Symbol). Named Secure nameOf -> Text
secureName Named Secure nameOf
nm = if Text -> Int
T.length (forall (style :: Symbol) (nameOf :: Symbol).
Named style nameOf -> Text
named Named Secure nameOf
nm) forall a. Ord a => a -> a -> Bool
< Int
5
then Int -> Text -> Text
T.replicate Int
8 Text
"#"
else ((Int -> Text -> Text
T.take Int
2 forall a b. (a -> b) -> a -> b
$ forall (style :: Symbol) (nameOf :: Symbol).
Named style nameOf -> Text
named Named Secure nameOf
nm)
forall a. Semigroup a => a -> a -> a
<> Int -> Text -> Text
T.replicate (Text -> Int
T.length (forall (style :: Symbol) (nameOf :: Symbol).
Named style nameOf -> Text
named Named Secure nameOf
nm) forall a. Num a => a -> a -> a
- Int
4) Text
"#"
forall a. Semigroup a => a -> a -> a
<> Text -> Text
T.reverse (Int -> Text -> Text
T.take Int
2 forall a b. (a -> b) -> a -> b
$ Text -> Text
T.reverse forall a b. (a -> b) -> a -> b
$ forall (style :: Symbol) (nameOf :: Symbol).
Named style nameOf -> Text
named Named Secure nameOf
nm))
secureNameBypass :: Named Secure nameOf -> Text
secureNameBypass :: forall (nameOf :: Symbol). Named Secure nameOf -> Text
secureNameBypass = forall (style :: Symbol) (nameOf :: Symbol).
Named style nameOf -> Text
named
instance NameText Secure where
nameText :: forall (nameOf :: Symbol). Named Secure nameOf -> Text
nameText = forall (nameOf :: Symbol). Named Secure nameOf -> Text
secureName
class ( KnownNat (AllowedNameType nameOf ntl)
, DisallowedNameType nameOf ntl ntl
)
=> ValidNames (nameOf :: Symbol) (ntl :: [Symbol]) where
validName :: Proxy ntl -> Name nameOf -> Text
instance ( KnownNat (AllowedNameType nty ntl)
, DisallowedNameType nty ntl ntl
)
=> ValidNames nty ntl where
validName :: Proxy ntl -> Name nty -> Text
validName Proxy ntl
_ = forall (nameOf :: Symbol). Name nameOf -> Text
name
type family AllowedNameType (nty :: Symbol) (ntl :: [Symbol]) :: Nat where
AllowedNameType nty (nty ': ntl) = 0
AllowedNameType nty (any ': ntl) = 1 + (AllowedNameType nty ntl)
class DisallowedNameType (nty :: Symbol) (okntl :: [Symbol]) (ntl :: [Symbol])
instance TypeError ('Text "Name '" ':<>: 'ShowType nty
':<>: 'Text "' not in allowed Names: " ':<>: 'ShowType ntl)
=> DisallowedNameType nty '[] ntl
instance DisallowedNameType nty (nty ': ntys) ntl
instance {-# OVERLAPPABLE #-} DisallowedNameType nty ntys ntl
=> DisallowedNameType nty (oty ': ntys) ntl