
Hi Lev Empty data declarations are often used for doing this (and extending to GADTs if necessary - GADTs are covered in the GHC user manual). Here's a simple revision of your code that doesn't use GADTs - the code is literate Haskell so you should be able to copy-paste it into a file with .lhs as its extension (writing in literate Haskell means I can run the code myself in GHCi as I'm writing it, thus hopefully not posting code that is full of errors). Because each constructor for your original CmdTiming data type carried the same data (just Time) the translation to use EmptyDataDecls was straight forward - if you had different variants for the constructors it would have been more work.
{-# LANGUAGE EmptyDataDecls #-}
module RASTime where
Some dummy Time type to make the compiler happy
type Time = Int
data RAS data CAS data PCH data ACT
data CmdTiming a = CmdTiming a Time deriving (Ord,Show,Eq)
data Command = RD_CMD {bank :: Int, col :: Int, timing :: CmdTiming RAS } | WR_CMD {bank :: Int, col :: Int} | ACT_CMD {bank :: Int, row :: Int} | PCH_CMD {bank :: Int}
Note with EmptyDataDecls now used in the Command type you can't derive Show.