-------------------------------------------------------------------------------- {-# LANGUAGE GADTs #-} -------------------------------------------------------------------------------- module Console.Garepinoh.Types ( Result , Prelude , Stack , El(..) , NonEmptyList(..) , Func(..) , Function(..) ) where -------------------------------------------------------------------------------- -- |'Result' is either an error message or a 'Stack'. type Result t = Either String (Stack t) -------------------------------------------------------------------------------- -- |A 'Prelude' is a list of pre-defined functions. type Prelude t = [Func t] -------------------------------------------------------------------------------- -- |A 'Stack' is (simulated by) a list of elements. type Stack t = [El t] -------------------------------------------------------------------------------- -- |An element is either... data El t = Va t -- ^ a value of type @t@, | Li [El t] -- ^ a list of elements, or | Fu (Func t) -- ^ a function instance Eq t => Eq (El t) where Va a == Va b = a == b Li a == Li b = a == b Fu a == Fu b = hd (symb a) == hd (symb b) _ == _ = False instance Show t => Show (El t) where show (Va n) = show n show (Li l) = show l show (Fu f) = show f -------------------------------------------------------------------------------- -- |'NonEmptyList' is a non-empty list. data NonEmptyList t = NEL { hd :: t -- ^ first element (head) of the (non-empty) list. , tl :: [t] -- ^ remaining part (tail) of the (non-empty) list. } -------------------------------------------------------------------------------- -- |A Function consists of: data Func t = Func { symb :: NonEmptyList String -- ^ a non-empty list of identifiers; , func :: [Function t] -- ^ a list (@[f_fst,f_snd,..,f_last@]) of -- primitive/undivisible 'Function's which are evaluated step-by-step. } instance Show (Func t) where show = hd . symb -------------------------------------------------------------------------------- -- |A primitive/undivisible 'Function' is one of: -- -- data Function t = Ele (El t) -- ^ an element 'El'; | Ref String -- ^ a reference to other functions; or | Fun (Prelude t -> Stack t -> Either String (Stack t)) -- ^ an actual primitive/pre-defined/hard-coded function.