fcf-containers-0.8.0: 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

>>> import qualified GHC.TypeLits as TL
>>> import           Fcf.Data.Nat

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

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 typeval val where Source #

Methods

fromType :: Proxy typeval -> val Source #

Instances

Instances details
KnownNat n => KnownVal (n :: Nat) Integer Source # 
Instance details

Defined in Fcf.Data.Reflect

Methods

fromType :: Proxy n -> Integer Source #

KnownNat n => KnownVal (n :: Nat) Int Source # 
Instance details

Defined in Fcf.Data.Reflect

Methods

fromType :: Proxy n -> Int Source #

KnownSymbol s => KnownVal (s :: Symbol) String Source # 
Instance details

Defined in Fcf.Data.Reflect

Methods

fromType :: Proxy s -> String Source #

KnownVal ('[] :: [(Nat, Nat)]) [(Int, Int)] Source # 
Instance details

Defined in Fcf.Data.Reflect

Methods

fromType :: Proxy '[] -> [(Int, Int)] Source #

KnownVal ('[] :: [(Nat, Symbol)]) [(Int, String)] Source # 
Instance details

Defined in Fcf.Data.Reflect

Methods

fromType :: Proxy '[] -> [(Int, String)] Source #

KnownVal ('[] :: [Nat]) [Integer] Source # 
Instance details

Defined in Fcf.Data.Reflect

Methods

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

KnownVal ('[] :: [Nat]) [Int] Source # 
Instance details

Defined in Fcf.Data.Reflect

Methods

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

KnownVal ('[] :: [Symbol]) [String] Source # 
Instance details

Defined in Fcf.Data.Reflect

Methods

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

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

Defined in Fcf.Data.Reflect

Methods

fromType :: Proxy '[] -> [Tree String] Source #

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

Defined in Fcf.Data.Reflect

Methods

fromType :: Proxy '[] -> [Tree Integer] Source #

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

Defined in Fcf.Data.Reflect

Methods

fromType :: Proxy '[] -> [Tree Int] Source #

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

Defined in Fcf.Data.Reflect

Methods

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

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

Defined in Fcf.Data.Reflect

Methods

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

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

Defined in Fcf.Data.Reflect

Methods

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

KnownVal mems [Integer] => KnownVal ('Set mems :: Set Nat) (Set Integer) Source # 
Instance details

Defined in Fcf.Data.Reflect

Methods

fromType :: Proxy ('Set mems) -> Set0 Integer Source #

KnownVal mems [Int] => KnownVal ('Set mems :: Set Nat) (Set Int) Source # 
Instance details

Defined in Fcf.Data.Reflect

Methods

fromType :: Proxy ('Set mems) -> Set0 Int Source #

KnownVal mems [String] => KnownVal ('Set mems :: Set Symbol) (Set String) Source # 
Instance details

Defined in Fcf.Data.Reflect

Methods

fromType :: Proxy ('Set mems) -> Set0 String Source #

(KnownNat n, KnownVal trees [Tree Integer]) => KnownVal ('Node n trees :: Tree Nat) (Tree Integer) Source # 
Instance details

Defined in Fcf.Data.Reflect

Methods

fromType :: Proxy ('Node n trees) -> Tree0 Integer Source #

(KnownNat n, KnownVal trees [Tree Int]) => KnownVal ('Node n trees :: Tree Nat) (Tree Int) Source # 
Instance details

Defined in Fcf.Data.Reflect

Methods

fromType :: Proxy ('Node n trees) -> Tree0 Int Source #

(KnownSymbol n, KnownVal trees [Tree String]) => KnownVal ('Node n trees :: Tree Symbol) (Tree String) Source # 
Instance details

Defined in Fcf.Data.Reflect

Methods

fromType :: Proxy ('Node n trees) -> Tree0 String Source #

(KnownNat n, KnownNat m, KnownVal nms [(Int, Int)]) => KnownVal ('(n, m) ': nms :: [(Nat, Nat)]) [(Int, Int)] Source # 
Instance details

Defined in Fcf.Data.Reflect

Methods

fromType :: Proxy ('(n, m) ': nms) -> [(Int, Int)] Source #

(KnownNat n, KnownSymbol m, KnownVal nms [(Int, String)]) => KnownVal ('(n, m) ': nms :: [(Nat, Symbol)]) [(Int, String)] Source # 
Instance details

Defined in Fcf.Data.Reflect

Methods

fromType :: Proxy ('(n, m) ': nms) -> [(Int, String)] Source #

(KnownNat n, KnownVal ns [Integer]) => KnownVal (n ': ns :: [Nat]) [Integer] Source # 
Instance details

Defined in Fcf.Data.Reflect

Methods

fromType :: Proxy (n ': ns) -> [Integer] Source #

(KnownNat n, KnownVal ns [Int]) => KnownVal (n ': ns :: [Nat]) [Int] Source # 
Instance details

Defined in Fcf.Data.Reflect

Methods

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

(KnownSymbol sym, KnownVal syms [String]) => KnownVal (sym ': syms :: [Symbol]) [String] Source # 
Instance details

Defined in Fcf.Data.Reflect

Methods

fromType :: Proxy (sym ': syms) -> [String] Source #

(KnownVal t (Tree String), KnownVal trees [Tree String]) => KnownVal (t ': trees :: [a]) [Tree String] Source # 
Instance details

Defined in Fcf.Data.Reflect

Methods

fromType :: Proxy (t ': trees) -> [Tree String] Source #

(KnownVal t (Tree Integer), KnownVal trees [Tree Integer]) => KnownVal (t ': trees :: [a]) [Tree Integer] Source # 
Instance details

Defined in Fcf.Data.Reflect

Methods

fromType :: Proxy (t ': trees) -> [Tree Integer] Source #

(KnownVal t (Tree Int), KnownVal trees [Tree Int]) => KnownVal (t ': trees :: [a]) [Tree Int] Source # 
Instance details

Defined in Fcf.Data.Reflect

Methods

fromType :: Proxy (t ': trees) -> [Tree Int] Source #

KnownVal pairs [(Int, Integer)] => KnownVal ('MapC pairs :: MapC Nat Integer) (Map Int Integer) Source # 
Instance details

Defined in Fcf.Data.Reflect

Methods

fromType :: Proxy ('MapC pairs) -> Map Int Integer Source #

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

Defined in Fcf.Data.Reflect

Methods

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

KnownVal pairs [(Int, String)] => KnownVal ('MapC pairs :: MapC Nat Symbol) (Map Int String) Source # 
Instance details

Defined in Fcf.Data.Reflect

Methods

fromType :: Proxy ('MapC pairs) -> Map Int String Source #

KnownVal pairs [(String, Integer)] => KnownVal ('MapC pairs :: MapC Symbol Integer) (Map String Integer) Source # 
Instance details

Defined in Fcf.Data.Reflect

Methods

fromType :: Proxy ('MapC pairs) -> Map String Integer Source #

KnownVal pairs [(String, Int)] => KnownVal ('MapC pairs :: MapC Symbol Nat) (Map String Int) Source # 
Instance details

Defined in Fcf.Data.Reflect

Methods

fromType :: Proxy ('MapC pairs) -> Map String Int Source #

KnownVal pairs [(String, String)] => KnownVal ('MapC pairs :: MapC Symbol Symbol) (Map String String) Source # 
Instance details

Defined in Fcf.Data.Reflect

Methods

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