{-# LANGUAGE DeriveFunctor, DeriveGeneric #-}
module GardGround.Syntax.Literal (
IntSz(..),
PrimTy(..),
Literal(..),
lookupBinder,
) where
import Data.Hashable (Hashable)
import Generic.Data (Generic)
import Numeric.Natural (Natural)
-- | integer sizes
data IntSz = PI8 | PI16 | PI32 | PI64 | PIsize
deriving (Show, Eq, Generic)
instance Hashable IntSz
-- | primitive type literals
data PrimTy = PtType | PtBool | PtString | PtIntSz | PtUnsInt IntSz | PtSigInt IntSz
deriving (Show, Eq, Generic)
instance Hashable PrimTy
-- | all possible literals
data Literal = LPrimTy PrimTy | LIntSz IntSz | LNat Natural
deriving (Show, Eq, Generic)
instance Hashable Literal
-- | lookup a value in a list by its position (via Natural instead of Int);
-- this is only here because it has no dependencies
lookupBinder :: [a] -> Natural -> Maybe a
lookupBinder = foldr ffun (const Nothing)
where
ffun x _ 0 = Just x
ffun _ r k = r (k-1)