eXistanCe
eXistanCe

Reputation: 735

Haskell : Generic type to generic and INT

I am developing a Stack module for a college project. Its suposed to be a list of generic "tokens" thus i used this constructor:

module Stack (Stack(S), dup, swap, pop, size) where

import Prelude

data Stack a = S [a]

But on the size operation, im suposed to add the size of the list to its head, like this:

size[1,2,3,4] = [4,1,2,3,4]

But i cant seem to define this function, since in the signature its receives a generic list and returns a generic list, but in reality its returning a generic list with an INT

size :: Stack a -> Stack a
size (S xs) = S(sizeAux xs)

sizeAux :: [a] -> [a]
sizeAux [] = [0]
sizeAux xs = length xs:xs

I have tried using Show like

sizeAux :: [a] -> [a]
sizeAux [] = ["0"]
sizeAux xs = show((length xs)):xs

but i get the same error, only this time with [Char]

Is there any way to bypass this without changing the Stack constructor to something like [String]? Any help will be apreciated thanks.

Upvotes: 0

Views: 368

Answers (3)

luqui
luqui

Reputation: 60533

I agree with @shinobi, that using an ADT is probably the best way to go. But I just want to bring your awareness to a sexy approach, which is to use a typed stack:

{-# LANGUAGE TypeOperators #-}

data Empty = Empty
data x :> xs = x :> xs
infixr 5 :>

class Stack a where sizeAux :: a -> Int
instance Stack Empty where sizeAux _ = 0
instance (Stack xs) => Stack (x :> xs) where 
    sizeAux (_ :> xs) = 1 + size xs

-- Here the head can be a different type from the rest of the stack,
-- and that is known statically.
size :: (Stack xs) => xs -> Int :> xs
size xs = sizeAux xs :> xs

dup :: x :> xs -> x :> x :> xs
dup (x :> xs) = x :> x :> xs

add :: Int :> Int :> xs -> Int :> xs
add (x :> y :> xs) = (x + y) :> xs

-- etc.

Upvotes: 2

freestyle
freestyle

Reputation: 3790

If you really want this, you can do like this:

import Data.List

size :: Num a => Stack a -> Stack a
size (S xs) = S (sizeAux xs)

sizeAux :: Num a => [a] -> [a]
sizeAux xs = genericLength xs : xs

Upvotes: 1

shinobi
shinobi

Reputation: 361

If you're trying to build a stack machine in the manner of FORTH, for example (as your specification of size suggests,) using [a] for the stack isn't likely to do the trick.

A simple and straightforward way to do it would be first to decide on what primitive data types your machine is going to work on, then create a data type with a constructor for each separate type, e.g.:

data Data = I Int | S String | Error String
    deriving Show -- for convenience only

Then, the state of your stack machine would be of type [Data] -- in this case, it would let you do computations on ints and strings, as well as handle errors "out-of-band".

Then your size operator would look like this:

size :: [Data] -> [Data]
size xs = I (length xs) : xs

Upvotes: 3

Related Questions