Thanks a lot! Those days I have read about "DataKinds" extension (with help
of Haskell-Cafe guys), and now I am able to understand your code. The
technique to connect the type-level and term-level integers allows to
duplicate information (duplicate information needed because of my more or
less clear requirements in my previous posts), but in a safe way (i.e. with
no copy/paste error): if I change "one" in "two" in the definition of the
smart constructor mkVector, I obtain an error, as expected because of the
use of type variable n on both sides of the equality in Tensor type
definition (and then we understand why the type constructor SNat has been
introduced).
This is a working example (this is not exactly what I will do at the end,
but it is very instructive! One more time, thanks!):
--------------------------------------
{-# LANGUAGE DataKinds, GADTs, KindSignatures, StandaloneDeriving #-}
data Nat = Zero | Succ Nat
type One = Succ Zero
type Two = Succ One
type Three = Succ Two
-- connects the type-level Nat with a term-level construct
data SNat :: Nat -> * where
SZero :: SNat Zero
SSucc :: SNat n -> SNat (Succ n)
deriving instance Show (SNat a)
zero = SZero
one = SSucc zero
two = SSucc one
three = SSucc two
data Tensor (n :: Nat) a = MkTensor { order :: SNat n, items :: [a] }
deriving Show
type Vector = Tensor One
type Matrix = Tensor Two
mkVector :: [a] -> Vector a
mkVector v = MkTensor { order = one, items = v }
-- some dummy operation defined between two Vectors (and not other order
-- tensors), which results in a Vector.
some_operation :: Num a => Vector a -> Vector a -> Vector a
some_operation (MkTensor { items = v1 }) (MkTensor { items = v2 }) =
mkVector (v1 ++ v2)
main = do
let va = mkVector ([1,2,3] :: [Integer])
let vb = mkVector ([4,5,6] :: [Integer])
print $ some_operation va vb
print $ order va
print $ order vb
---------------------------------