[Haskell-cafe] using the same data structure on a type level and as a value

Zoran BoĆĄnjak zoran.bosnjak at via.si
Sat Feb 15 12:51:36 UTC 2025


Dear haskellers,
I would like to reuse some (complex) data structures at a type level and 
as a regular value. The intention is to have the original specification 
on the type level (something like web API in Servant). But the idea is 
also to be able to convert the same structure to the value (of the same 
shape) and print it for example. There is no need to go from values back 
to types. I am not sure if Generic could help me do the conversion or do 
I need Typeable or even something else. I would like to avoid template 
haskell if possible, but please do advice if TH is the way to go in such 
cases.

In my case, the data type structure is suppose to be the same, with the 
only difference being the 2 "primitives", which is: number is (Nat or 
Integer, depending on the usecase) and text is (Symbol or String).

My attempt was something like this.

import           GHC.Generics -- not sure if this is required, but 
deriving works OK
import           GHC.TypeLits

data Usecase = TypeLevel | ValueLevel

-- Generic Int is 'Nat' or 'Integer'.
type family GInt (u :: Usecase) where
     GInt 'TypeLevel = Nat
     GInt 'ValueLevel = Integer

-- Generic Text is 'Symbol' or 'Text'.
type family GText (u :: Usecase) where
     GText 'TypeLevel = Symbol
     GText 'ValueLevel = String

-- Positive/zero or negative value.
data PlusMinus = Plus | Minus deriving (Generic, Show)

-- Now we can define generic plus/minus number.
data PMInt (u :: Usecase) = PMInt PlusMinus (GInt u)
     deriving (Generic)

deriving instance Show (PMInt 'ValueLevel)

-- And we also define some more complex structure.
data GNumber (u :: Usecase)
     = GNumInt (PMInt u)
     | GNumDiv (GNumber u) (GNumber u)
     | GNumPow (PMInt u) (PMInt u)
     deriving (Generic)

deriving instance Show (GNumber 'ValueLevel)

data GTest (u :: Usecase) = GTest [GInt u] [GText u]
     deriving (Generic)

deriving instance Show (GTest 'ValueLevel)

-- This does not work, but the idea is to define some type aliases
-- In real application, this will be a huge list of structure 
descriptions (as types)
type Example1 = 'PMInt 'Plus 3 -- GHC does not like '3' here??
type Example2 = 'PMInt 'Minus 4
type Example3 = 'GNumInt Example1
type Example4 = 'GNumDiv Example3 Example3
type Example5 = 'GTest '[ 1, 2, 3 ] '[ "Test1", "Test2"]

-- 'convert' implementation ??

-- ... and be able to convert types to values, something like this
val1 :: PMInt 'ValueLevel
val1 = convert @Example1

-- ... or print it directly
f :: IO ()
f = print
   ( convert @Example1, convert @Example2, convert @Example3
   , convert @Example4, convert @Example5)

Appreciate your suggestions.

regards,
Zoran


More information about the Haskell-Cafe mailing list