fcf-containers-0.8.2: Data structures and algorithms for first-class-families
Copyright(c) gspia 2023-
LicenseBSD
Maintainergspia
Safe HaskellSafe-Inferred
LanguageHaskell2010

Fcf.Data.Reflect

Description

Fcf.Data.Reflect

Helpers to get results from type-level computations into the fromType-level.

Synopsis

Documentation

class KnownNats (ns :: [Nat]) where Source #

Deprecated: Replaced with KnownVal

Reflect a list of Nats

Note that you may also use the KnownVal methods given below.

This method is taken from https://hackage.haskell.org/package/numhask-array-0.10.1/docs/src/NumHask.Array.Shape.html#natVals

Example

Expand
:{

afun :: forall n. (n ~ '[1,2,3,4]) => [Int] afun = natVals @n Proxy :}

afun
1,2,3,4

Methods

natVals :: Proxy ns -> [Int] Source #

Instances

Instances details
KnownNats ('[] :: [Nat]) Source # 
Instance details

Defined in Fcf.Data.Reflect

Methods

natVals :: Proxy '[] -> [Int] Source #

(KnownNat n, KnownNats ns) => KnownNats (n ': ns) Source # 
Instance details

Defined in Fcf.Data.Reflect

Methods

natVals :: Proxy (n ': ns) -> [Int] Source #

class KnownVal val kind where Source #

Methods

fromType :: Proxy kind -> val Source #

Instances

Instances details
(KnownNat n, Num a) => KnownVal a (n :: Nat) Source # 
Instance details

Defined in Fcf.Data.Reflect

Methods

fromType :: Proxy n -> a Source #

KnownVal () '() Source # 
Instance details

Defined in Fcf.Data.Reflect

Methods

fromType :: Proxy '() -> () Source #

KnownVal Bool 'False Source # 
Instance details

Defined in Fcf.Data.Reflect

KnownVal Bool 'True Source # 
Instance details

Defined in Fcf.Data.Reflect

Methods

fromType :: Proxy 'True -> Bool Source #

(IsString str, KnownSymbol s) => KnownVal str (s :: Symbol) Source # 
Instance details

Defined in Fcf.Data.Reflect

Methods

fromType :: Proxy s -> str Source #

(IsString str, Typeable typ) => KnownVal str (typ :: Type) Source # 
Instance details

Defined in Fcf.Data.Reflect

Methods

fromType :: Proxy typ -> str Source #

(IsString str, KnownSymbol sym) => KnownVal str ('Text sym :: ErrorMessage) Source # 
Instance details

Defined in Fcf.Data.Reflect

Methods

fromType :: Proxy ('Text sym) -> str Source #

(IsString str, KnownSymbol sym) => KnownVal str ('Text sym :: Text) Source #

Text instance.

Example

Expand
import qualified Data.Text as Txt
:{

afun :: forall r. (r ~ 'FTxt.Text "hmm") => Txt.Text afun = fromType (Proxy @r) :}

afun

"hmm"

Instance details

Defined in Fcf.Data.Reflect

Methods

fromType :: Proxy ('Text sym) -> str Source #

(IsString str, KnownVal str err1, KnownVal str err2, Semigroup str) => KnownVal str (err1 :$$: err2 :: ErrorMessage) Source # 
Instance details

Defined in Fcf.Data.Reflect

Methods

fromType :: Proxy (err1 :$$: err2) -> str Source #

(IsString str, KnownVal str err1, KnownVal str err2, Semigroup str) => KnownVal str (err1 :<>: err2 :: ErrorMessage) Source # 
Instance details

Defined in Fcf.Data.Reflect

Methods

fromType :: Proxy (err1 :<>: err2) -> str Source #

(IsString str, Typeable typ) => KnownVal str ('ShowType typ :: ErrorMessage) Source # 
Instance details

Defined in Fcf.Data.Reflect

Methods

fromType :: Proxy ('ShowType typ) -> str Source #

KnownVal [(Int, val)] pairs => KnownVal (IntMap val) (pairs :: [(Nat, val')]) Source # 
Instance details

Defined in Fcf.Data.Reflect

Methods

fromType :: Proxy pairs -> IntMap val Source #

(Ord val, KnownVal [val] kind) => KnownVal (Set val) (kind :: [kind']) Source # 
Instance details

Defined in Fcf.Data.Reflect

Methods

fromType :: Proxy kind -> Set val Source #

KnownVal (Maybe a1) ('Nothing :: Maybe a) Source # 
Instance details

Defined in Fcf.Data.Reflect

Methods

fromType :: Proxy 'Nothing -> Maybe a1 Source #

KnownVal [a] ('[] :: [k]) Source # 
Instance details

Defined in Fcf.Data.Reflect

Methods

fromType :: Proxy '[] -> [a] Source #

KnownVal [(Int, val)] pairs => KnownVal (IntMap val) ('NatMap pairs :: NatMap v) Source # 
Instance details

Defined in Fcf.Data.Reflect

Methods

fromType :: Proxy ('NatMap pairs) -> IntMap val Source #

(Ord val, KnownVal [val] kind) => KnownVal (Set val) ('Set kind :: Set a) Source # 
Instance details

Defined in Fcf.Data.Reflect

Methods

fromType :: Proxy ('Set kind) -> Set0 val Source #

KnownVal a2 a3 => KnownVal (Maybe a2) ('Just a3 :: Maybe a1) Source # 
Instance details

Defined in Fcf.Data.Reflect

Methods

fromType :: Proxy ('Just a3) -> Maybe a2 Source #

(KnownVal val k, KnownVal (Forest val) trees) => KnownVal (Tree val) ('Node k trees :: Tree a) Source # 
Instance details

Defined in Fcf.Data.Reflect

Methods

fromType :: Proxy ('Node k trees) -> Tree0 val Source #

(KnownVal val x, KnownVal [val] xs) => KnownVal [val] (x ': xs :: [a]) Source # 
Instance details

Defined in Fcf.Data.Reflect

Methods

fromType :: Proxy (x ': xs) -> [val] Source #

(Ord key, KnownVal [(key, val)] pairs) => KnownVal (Map key val) (pairs :: [(key', val')]) Source # 
Instance details

Defined in Fcf.Data.Reflect

Methods

fromType :: Proxy pairs -> Map key val Source #

KnownVal b2 b3 => KnownVal (Either a1 b2) ('Right b3 :: Either a b1) Source # 
Instance details

Defined in Fcf.Data.Reflect

Methods

fromType :: Proxy ('Right b3) -> Either a1 b2 Source #

KnownVal a2 a3 => KnownVal (Either a2 b1) ('Left a3 :: Either a1 b) Source # 
Instance details

Defined in Fcf.Data.Reflect

Methods

fromType :: Proxy ('Left a3) -> Either a2 b1 Source #

(Ord key, KnownVal [(key, val)] pairs) => KnownVal (Map key val) ('MapC pairs :: MapC k v) Source # 
Instance details

Defined in Fcf.Data.Reflect

Methods

fromType :: Proxy ('MapC pairs) -> Map key val Source #

(KnownVal a1 a, KnownVal b1 b) => KnownVal (a1, b1) ('(a, b) :: (k1, k2)) Source # 
Instance details

Defined in Fcf.Data.Reflect

Methods

fromType :: Proxy '(a, b) -> (a1, b1) Source #

(KnownVal a1 a, KnownVal b1 b, KnownVal c1 c) => KnownVal (a1, b1, c1) ('(a, b, c) :: (k1, k2, k3)) Source # 
Instance details

Defined in Fcf.Data.Reflect

Methods

fromType :: Proxy '(a, b, c) -> (a1, b1, c1) Source #

(KnownVal a1 a, KnownVal b1 b, KnownVal c1 c, KnownVal d1 d) => KnownVal (a1, b1, c1, d1) ('(a, b, c, d) :: (k1, k2, k3, k4)) Source # 
Instance details

Defined in Fcf.Data.Reflect

Methods

fromType :: Proxy '(a, b, c, d) -> (a1, b1, c1, d1) Source #

(KnownVal a1 a, KnownVal b1 b, KnownVal c1 c, KnownVal d1 d, KnownVal e1 e) => KnownVal (a1, b1, c1, d1, e1) ('(a, b, c, d, e) :: (k1, k2, k3, k4, k5)) Source # 
Instance details

Defined in Fcf.Data.Reflect

Methods

fromType :: Proxy '(a, b, c, d, e) -> (a1, b1, c1, d1, e1) Source #