module Lang.Hask.Time where

import FP
import GHC.TypeLits
import qualified FP.Pretty as P

class Time ψ τ | τ -> ψ where
  tzero :: τ
  tick :: ψ -> τ -> τ

-- Concrete
newtype  ψ =  [ψ]
  deriving (Eq, Ord, Pretty, Container ψ, Iterable ψ, Buildable ψ)
instance Bot ( ψ) where bot = nil
instance Time ψ ( ψ) where { tzero = bot ; tick = (&) }
 :: P 
 = P

-- kCFA
newtype  (k :: Nat) ψ =  [ψ]
  deriving (Eq, Ord, Pretty, Container ψ, Iterable ψ, Buildable ψ)
instance Bot ( k ψ) where bot = nil
instance (KnownNat k) => Time ψ ( k ψ) where
  tzero = bot
  tick x y = fromList $ firstN (natVal (P :: P k)) $ toList $ x & y
 :: P ( 1)
 = P

-- 0CFA
data  ψ = 
  deriving (Eq, Ord)
instance Pretty ( a) where
  pretty  = P.lit "∙"
instance Bot ( ψ) where bot = 
instance Time ψ ( ψ) where { tzero = bot ; tick = const id }
 :: P 
 = P