[Haskell-cafe] difference between type and newtype

Andrea Rossato mailing_list at istitutocolli.org
Sat Aug 26 07:53:23 EDT 2006


Il Sat, Aug 26, 2006 at 11:55:34AM +0100, Brian Hulley ebbe a scrivere:
> Yes, it's useful because it allows you to make a distinction between 
> different uses of the same type of function and make these different uses 
> into instances of different classes. It also allows you to hide the fact 
> that a function is being used. Such decls are often used in monadic 
> programming, for example if you look at the library docs for 
> Control.Monad.State you will see the following decl:
> 
>    newtype State s a = State {runState :: (s -> (a,s))}
> ie
>    newtype State s a = State (s -> (a,s))
> 

this is what I'm trying to do, sort of: turn the code at the button
into the do-notation.[1]

> Consider:
> 
>        type T a = a -> Int
> 
>        data D a = D (a -> Int)
> 
>        newtype N a = N (a -> Int)
> 

Now this is perfectly clear, with the _|_ part too (sort of...;-).

So:
newtype T1 a = T1 (Int -> (a,Int))

mkT1 a = T1 (\x -> (a, x))
applyT1 (T1 a) x = a x 
makeT1 a b = applyT1 (mkT1 a) b

Thank you very much.
Andrea


[1] the code follows:

module StateOutputMonad where
data Term = Con Int
          | Add Term Term
            deriving (Show)

type MSO a = State -> (a, State, Output)
type State = Int
type Output = String

formatLine :: Term -> Int -> Output
formatLine t a = "eval (" ++ show t ++ ") <= " ++ show a ++ " - "                                                       



mkMSO :: a -> MSO a
mkMSO a = \s -> (a, s, "")

bindMSO :: MSO a -> (a -> MSO b) -> MSO b
bindMSO m f = \x -> 
             let (a, y, s1) = m x in
             let (b, z, s2) = f a y in
             (b, z, s1 ++ s2)

combineMSO :: MSO a -> MSO b -> MSO b
combineMSO m f = m `bindMSO` \_ -> f

incMSOstate :: MSO ()
incMSOstate = \s -> ((), s + 1, "")

outMSO :: Output -> MSO ()
outMSO = \x s -> ((),s, x)

evalMSO :: Term -> MSO Int
evalMSO (Con a) = incMSOstate `combineMSO` 
                  outMSO (formatLine (Con a) a) `combineMSO` 
                  mkMSO a
evalMSO (Add t u) =  evalMSO t `bindMSO` \a ->
                     evalMSO u `bindMSO` \b ->
                     incMSOstate `combineMSO` 
                     outMSO (formatLine (Add t u) (a + b)) `combineMSO`
                     mkMSO (a + b)


-- To be tested with:
-- evalMSO (Add (Con 6) (Add (Con 16) (Add (Con 20) (Con 12)))) 0
 


More information about the Haskell-Cafe mailing list