I've found a way to convert a Nat
into an Integer
using Proxy
and natVal
as you can see in the code below:
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE ScopedTypeVariables #-}
module Main where
import Data.Proxy (Proxy)
import Data.Monoid ((<>))
import GHC.TypeLits
main :: IO ()
main = do
fromNat (undefined :: Proxy 5)
fromNat :: KnownNat n => Proxy n -> IO ()
fromNat proxy = do
let (num :: Integer) = natVal proxy -- converting a Nat to an Integer
putStrLn $ "Some num: " <> show num
But I'm not able to think a straightforward way to convert a type List into a regular list, the code below doesn't even type check:
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE ScopedTypeVariables #-}
module Main where
import Data.Proxy (Proxy)
import Data.Monoid ((<>))
import GHC.TypeLits
main :: IO ()
main = do
fromNat (undefined :: Proxy 5)
fromListNat (undefined :: Proxy '[2,3,10])
fromNat :: KnownNat n => Proxy n -> IO ()
fromNat proxy = do
let (num :: Integer) = natVal proxy -- converting a Nat to an Integer
putStrLn $ "Some num: " <> show num
fromListNat :: Proxy [Nat] -> IO ()
fromListNat = undefined
How can I convert a type list into a regular list?
The answer is to make something like KnownNat
but for type level lists of Nat
. We proceed by induction on the type-level list, using a type class. This typeclass, through its superclass constraints, will check that all elements of you list satisfy KnownNat
and then it will use that fact to reconstruct a term-level list.
{-# LANGUAGE TypeOperators, KindSignatures #-}
-- Similar to `KnownNat (n :: Nat)`
class KnownNatList (ns :: [Nat]) where
natListVal :: proxy ns -> [Integer]
-- Base case
instance KnownNatList '[] where
natListVal _ = []
-- Inductive step
instance (KnownNat n, KnownNatList ns) => KnownNatList (n ': ns) where
natListVal _ = natVal (Proxy :: Proxy n) : natListVal (Proxy :: Proxy ns)
Then, fromListNat
takes the same shape as fromNat
:
fromListNat :: KnownNatList ns => Proxy ns -> IO ()
fromListNat proxy = do
let (listNum :: [Integer]) = natListVal proxy
putStrLn $ "Some list of num: " <> show listNum
Splicing in these changes to your initial code, I get the expected output:
$ ghc Main.hs
$ ./Main
Some num: 5
Some list of num: [2,3,10]