difference between type and newtype

Hello! I cannot understand this piece of code: type Z = Int type T a = Z -> (a, Z) newtype T1 a = T1 (Z -> (a,Z)) mkT :: a -> T a mkT a = \x -> (a, x) mkT1 :: a -> b -> (a,b) mkT1 a = \x -> (a, x) why mkT is a type constructor and mkT1 seems not to be? thanks for your kind attention. Andrea

Hi
type Z = Int Here you can replace all occurances of Z with Int, and its exactly the same program.
newtype T1 a = T1 (Z -> (a,Z)) newtype T1 a is the same as data T1 a
why mkT is a type constructor and mkT1 seems not to be? In what way is mkT a type constructor? In this program only T1 is a type constructor, as far as I can see.
Thanks Neil

Il Fri, Aug 25, 2006 at 07:52:35PM +0100, Neil Mitchell ebbe a scrivere:
why mkT is a type constructor and mkT1 seems not to be? In what way is mkT a type constructor? In this program only T1 is a type constructor, as far as I can see.
read my sentence as "why T is a type constructor and T1 seems not to be?" look at the types: mkT 2 5 will return (2,5) whose type is "T a" mkT1 2 5 will return (2,5) whose type is "(a,b)". they return the same stuff with different types. Onle myT will return a type of type "T a". andrea

Hi
(2,5) whose type is "T a"
No, try expanding the type synonyms: mkT :: a -> T a mkT :: a -> Z -> (a, Z) mkT :: a -> Int -> (a, Int) The type of (2,5) is (a, Int), or in this specific case (Int, Int).
they return the same stuff with different types. Onle myT will return a type of type "T a". The type T is only a type alias, everywhere you can see T you can rewrite it. If mkT1 is applied to one argument, which is an Int, then you have a type T as a result.
For example, the type of "Test" is all of FilePath, [Char], String - all at the same time, since they are aliases for each other. Thanks Neil

Andrea Rossato wrote:
Hello!
I cannot understand this piece of code:
type Z = Int type T a = Z -> (a, Z) newtype T1 a = T1 (Z -> (a,Z))
mkT :: a -> T a mkT a = \x -> (a, x)
Hi Andrea, The definition of mkT above is identical to just writing: mkT :: a -> (Z -> (a,Z)) which in turn is identical to: mkT :: a -> (Int -> (a, Int)) ie mkT :: a -> Int -> (a, Int) because type decls just introduce a shorthand notation whose meaning is equivalent to substituting the right hand side of the type decl into the places in your code where you write T a or Z.
mkT1 :: a -> b -> (a,b) mkT1 a = \x -> (a, x)
why mkT is a type constructor and mkT1 seems not to be?
mkT1 above is not a type constructor either. If you want to construct a value of the newtype T1 a then you would have to write: mkT1 :: a -> T1 a mkT1 a = T1 (\x -> (a,x)) In the above, the occurrence of T1 in the signature is called a type constructor, and the occurrence of T1 in T1(\x -> (a,x)) is just called a constructor (or "value constructor"). mkT1 is a function that constructs a value of type (T1 a) and so could perhaps also be called a value constructor although this would be unusual - usually the term is only used to describe the constructor specified on the rhs of the newtype (or constructors specified in the data) declaration. It is maybe easier to just think of a newtype decl as being the same as a data decl except for the fact that you can only have one constructor on the rhs whereas a data decl allows multiple constructors, and a type decl by contrast as just introducing a simple alias for convenience. (There are in fact two differences between a newtype decl and a data decl with 1 constructor but it's probably best to understand the above distinction between newtype/data vs type first) Regards, Brian. -- Logic empowers us and Love gives us purpose. Yet still phantoms restless for eras long past, congealed in the present in unthought forms, strive mightily unseen to destroy us. http://www.metamilk.com

Il Fri, Aug 25, 2006 at 08:35:01PM +0100, Brian Hulley ebbe a scrivere:
It is maybe easier to just think of a newtype decl as being the same as a data decl except for the fact that you can only have one constructor on the rhs whereas a data decl allows multiple constructors, and a type decl by contrast as just introducing a simple alias for convenience.
First my apologies for being a bit confusing in my question: I'm tired and wrote the code too quickly...;-) So I'll rephrase: type T a = Int -> (a, Int) mkT :: a -> T a mkT a = \x -> (a, x) newtype T1 a = T1 (Int -> (a,Int)) mkT1 :: a -> T1 a mkT1 a = T1 (\x -> (a, x)) data T2 a = T2 (Int -> (a,Int)) mkT2 :: a -> T2 a mkT2 a = T2 (\x -> (a, x)) makeT a b = mkT a b --makeT1 a b = mkT1 a b --makeT2 a b = mkT2 a b why makeT 1 2 works while makeT1 a makeT2 will not compile? That is to say: why mkT1 and mkT2 cannot be used (even though the compiler does not complain)? That is to say, can someone explain this behaviour? I do not grasp it. Thanks for your kind attention. Andrea

Am Freitag, 25. August 2006 23:55 schrieb Andrea Rossato:
Il Fri, Aug 25, 2006 at 08:35:01PM +0100, Brian Hulley ebbe a scrivere:
It is maybe easier to just think of a newtype decl as being the same as a data decl except for the fact that you can only have one constructor on the rhs whereas a data decl allows multiple constructors, and a type decl by contrast as just introducing a simple alias for convenience.
First my apologies for being a bit confusing in my question: I'm tired and wrote the code too quickly...;-)
So I'll rephrase:
type T a = Int -> (a, Int) mkT :: a -> T a mkT a = \x -> (a, x)
newtype T1 a = T1 (Int -> (a,Int)) mkT1 :: a -> T1 a mkT1 a = T1 (\x -> (a, x))
data T2 a = T2 (Int -> (a,Int)) mkT2 :: a -> T2 a mkT2 a = T2 (\x -> (a, x))
makeT a b = mkT a b --makeT1 a b = mkT1 a b --makeT2 a b = mkT2 a b
why makeT 1 2 works while makeT1 a makeT2 will not compile? That is to say: why mkT1 and mkT2 cannot be used (even though the compiler does not complain)? That is to say, can someone explain this behaviour? I do not grasp it.
Because T a is a function type, namely Int -> (a,Int), so if a has type ta, mkT a has type Int -> (ta,Int) and so can be applied to a further argument: makeT a b = (mkT a) b is fine. However, neither T1 a nor T2 a is a function type, a value of type T1 a is a function _wrapped by the data (or value) constructor T1_ (the same applies to T2, of course), so before you can apply mkT1 a to an Int, you have to unwrap it: unT1 :: T1 a -> T a unT1 (T1 f) = f makeT1 a b = unT1 (mkT1 a) b will work fine. HTH, Daniel
Thanks for your kind attention. Andrea _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- "In My Egotistical Opinion, most people's C programs should be indented six feet downward and covered with dirt." -- Blair P. Houghton

Il Sat, Aug 26, 2006 at 01:27:38AM +0200, Daniel Fischer ebbe a scrivere:
Because T a is a function type, namely Int -> (a,Int), so ...
iHowever, neither T1 a nor T2 a is a function type, a value of type T1 a is a function _wrapped by the data (or value) constructor T1_ (the same applies to T2, of course), so before you can apply mkT1 a to an Int, you have to unwrap it:
so, if I understand correctly, mkT is just a partial application *becase* of its "fake" type signature... that's a bit confusing... also because that "type" cannot be instance of a class. moreover why it is possible to declare something like this? data T2 a = T2 (Int -> (a,Int)) is there any usefulness? I hoped it could work as with types declared with "type". perhaps this is silly, but it is not possible to declare function types? could you please indicate me some documentation that explains this kind of stuff? So far I didn't find anything on that. Thank you. Andrea

Il Sat, Aug 26, 2006 at 02:02:36AM +0200, Andrea Rossato ebbe a scrivere:
perhaps this is silly, but it is not possible to declare function types?
could you please indicate me some documentation that explains this kind of stuff? So far I didn't find anything on that.
well, I've found something in the Report: 6.1.6 Function Types Functions are an abstract type: no constructors directly create functional values. The following simple functions are found in the Prelude: id, const, (.), flip, ($), and until. Now I'm trying to understand what "directly" stands for... andrea

Hello Andrea, Saturday, August 26, 2006, 1:44:19 PM, you wrote:
perhaps this is silly, but it is not possible to declare function types?
could you please indicate me some documentation that explains this kind of stuff? So far I didn't find anything on that.
well, I've found something in the Report:
btw, i don't think that Report can be used to learn language, it's better to look into various tutorials or, even better, textbooks
6.1.6 Function Types Functions are an abstract type: no constructors directly create functional values. The following simple functions are found in the Prelude: id, const, (.), flip, ($), and until.
Now I'm trying to understand what "directly" stands for...
it's not something related to your question: Reports says here about functional values, not types :) i will try to make explanation you need. first, Haskell has a few primitive datatypes - Char, Int, Bool... second, it provides a way to construct new datatypes: data T = C1 Int Char | C2 Bool here, T is new type whose values can be constructed _only_ using C1 or C2 constructor. to be exact, we can construct value of type T, we can either apply C2 to value of another type, Bool, f.e. "C2 True", or by applying C1 to two values, Int and Char, f.e. C1 5 'a' 'newtype' declaration is equivalent to 'data', it just have some limitations 'type' _don't_ constructs any new type, it just adds type _synonym_ with sole purpose to simplify using of complex type constructions (it's just like 'typedef' in C if you know this language) for example, type String = [Char] allows us to use String in function signatures instead of [Char] Declarations of new types can have parameters: data T a b = C1 a b | C2 a Such declaration effectively declares a _family_ of different types what can be constructed by applying T2 type constructor to concrete types, f.e. "T2 Int String", "T2 Int Int" or even "T2 (T2 Int Int) String" In addition to predefined types (Int, Bool and so on) there are a number of predefined type constructors. Some of them are defined in Haskell itself: data Either a b = Left a | Right b data Maybe a = Just a | Nothing data [a] = a : [a] | [] Last definition is a bit artificial, but modulo specific syntax, list type constructor can be defined in Haskell proper: data List a = Cons a (List a) | Nil Function is among predefined type constructors, but it cannot be defined using Haskell itself: data (->) a b = .... But in all other aspects, '->' can be seen as ordinal type constructor which has two type parameters. This means that you don't need nor can't to define _new_ functional types using 'data' definition. But you can and should use type synonym declarations when you need to "specialize" (->) type constructor, i.e. give name to some concrete functional type, f.e. type HashFunction = (String->Int) This synonym can then be used in type specification like the right part in its definition, i.e. declarations createHash :: HashFunction -> IO Hash and createHash :: (String->Int) -> IO Hash are equivalent. So, technically speaking, you can't declare function types, there is only one predefined type constructor that can construct any function type you need. But from practical POV, you can define synonyms for any function type you've constructed using '->'. If you want, you can also declare parametric type synonyms: type HashFunction a = (a->Int) or something like type CPS a b = a -> Either a b It should be obvious that using parametric synonyms don't differ from using parameterless ones: createHash :: HashFunction Char -> IO (Hash Char) is translated into createHash :: (Char->Int) -> IO (Hash Char) Next point is that in Haskell functions are first-class values, i.e. you can hold them in data structures, pass as parameters to other functions and even return them as results. For example, the following function accepts function of type String->Int->Int and returns function of type (Int->Int): func :: (String->Int->Int) -> (Int->Int) func f = f "" The following data type includes function as one of its fields: data T = C (String->Int->Int) Int As i already said, newtype is just limited form of 'data' declaration, one which should use exactly one constructor with exactly one field, for example: newtype I = I Int Such restrictions guarantee that new type defined may use the same representation as its only field, and in fact newtype language construct guarantees it. But it is only internal representation, from the programmer's POV newtype is don't differs from 'data' Of course, newtype can also be used to define type whose only field contains some function: newtype F = F (String->Int) Again, in this case language guarantees that internal F representation will be the same as for plain (Int->String) function and therefore the same as for type synonym: type S = String->Int But from programmer POV, the difference still holds: while S denotes function of given type and can be used interchangeably with full notion of this function type, F is just the type which internally contains such function. Values of type F can be constructed, as for any other data type, only using F data constructor applied to function of corresponding type, f.e. "F length". So, "F length" has type F while 'length' itself may have type "String->Int" whose synonym is S hope that it helps :) -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

Il Sat, Aug 26, 2006 at 06:00:02PM +0400, Bulat Ziganshin ebbe a scrivere:
type HashFunction = (String->Int) ... createHash :: HashFunction -> IO Hash and createHash :: (String->Int) -> IO Hash
are equivalent. So, technically speaking, you can't declare function types, there is only one predefined type constructor that can construct any function type you need. But from practical POV, you can define synonyms for any function type you've constructed using '->'.
this possibility (POV) lead me to think it was possible to have a type constructor that could construct a function type.
Next point is that in Haskell functions are first-class values, i.e. you can hold them in data structures, pass as parameters to other functions and even return them as results. For example, the following function accepts function of type String->Int->Int and returns function of type (Int->Int):
func :: (String->Int->Int) -> (Int->Int) func f = f ""
ok, I've got it.
Of course, newtype can also be used to define type whose only field contains some function:
newtype F = F (String->Int)
Again, in this case language guarantees that internal F representation will be the same as for plain (Int->String) function and therefore the same as for type synonym:
type S = String->Int
But from programmer POV, the difference still holds: while S denotes function of given type and can be used interchangeably with full notion of this function type, F is just the type which internally contains such function.
As I said in a previous message it took me almost two day to grasp this distinction.
hope that it helps :)
sure it does! thank you very mu! andrea

Hello Andrea, Saturday, August 26, 2006, 6:40:06 PM, you wrote:
Of course, newtype can also be used to define type whose only field contains some function:
newtype F = F (String->Int)
Again, in this case language guarantees that internal F representation will be the same as for plain (Int->String) function and therefore the same as for type synonym:
type S = String->Int
But from programmer POV, the difference still holds: while S denotes function of given type and can be used interchangeably with full notion of this function type, F is just the type which internally contains such function.
As I said in a previous message it took me almost two day to grasp this distinction.
'newtype' construction was added exactly to allow definition of new distinctive types with the same 'contents' as existing ones. as Udo already stated, this may be required for hiding representation or just to define specific instance for some specific type that you use in your program i highly recommend you to look at "Haskell history" paper, http://haskell.org/haskellwiki/History_of_Haskell . Wadler was its coauthor and this paper written in the same clear and concise way as his papers. Part II of the paper makes an excellent overview of features that makes Haskell so special, including brief overview of various monads and story that precedes inclusion of newtype in Haskell 1.3 -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

Andrea Rossato wrote:
Il Sat, Aug 26, 2006 at 01:27:38AM +0200, Daniel Fischer ebbe a scrivere:
Because T a is a function type, namely Int -> (a,Int), so ...
iHowever, neither T1 a nor T2 a is a function type, a value of type T1 a is a function _wrapped by the data (or value) constructor T1_ (the same applies to T2, of course), so before you can apply mkT1 a to an Int, you have to unwrap it:
so, if I understand correctly, mkT is just a partial application *becase* of its "fake" type signature...
Yes that's right.
that's a bit confusing... also because that "type" cannot be instance of a class. moreover why it is possible to declare something like this? data T2 a = T2 (Int -> (a,Int))
is there any usefulness?
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))
I hoped it could work as with types declared with "type".
You probably know this but just in case, a newtype decl gives you the same advantages as a "type" decl in terms of speed, since there is no runtime overhead, but it also gives you the same advantages as a data decl in terms of enforcing distinctions between things that have the same form but different meaning in your program.
perhaps this is silly, but it is not possible to declare function types?
Consider: type T a = a -> Int data D a = D (a -> Int) newtype N a = N (a -> Int) In the "type" decl, you've simply made (T a) synonym for (a -> Int) so both type expressions are treated as identical by the compiler. With the "data" decl, you've introduced a new type of entity, (D a), which needs to be explicitly unwrapped (ie by pattern matching against (D fun)) to access the function. This allows you to make values of type (D a) an instance of a class and enforce a distinction between this particular use of functions from (a) to Int, without worrying that some other part of the program is going to mess everything up. But there is also a runtime penalty to pay because of the indirection through the D constructor. However with the "newtype" decl, you get the best of both worlds - no runtime cost but still allowing you to enforce the fact that the entity (N a) can't be confused with anything else in your program.
could you please indicate me some documentation that explains this kind of stuff? So far I didn't find anything on that.
I recommend chapter 8 of "Yet another Haskell Tutorial" which can be downloaded from http://www.haskell.org/haskellwiki/Books_and_tutorials#.E2.80.9CReal_world.E... If you still need more detail there's always section 4.2 of the Haskell98 report at http://haskell.org/onlinereport/decls.html which includes an example illustrating the subtle difference between newtype and data decls that is glossed over in 8.2 of YAHT (warning: may cause sleepless nights but definitely worth the effort ;-) ) Regards, Brian. -- Logic empowers us and Love gives us purpose. Yet still phantoms restless for eras long past, congealed in the present in unthought forms, strive mightily unseen to destroy us. http://www.metamilk.com

Brian Hulley wrote:
I recommend chapter 8 of "Yet another Haskell Tutorial" which can be downloaded from http://www.haskell.org/haskellwiki/Books_and_tutorials#.E2.80.9CReal_world.E...
Sorry - the correct part of the wiki page is: http://www.haskell.org/haskellwiki/Books_and_tutorials#Introductions_to_Hask...

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

Andrea Rossato wrote:
this is what I'm trying to do, sort of: turn the code at the button into the do-notation.[1]
type MSO a = State -> (a, State, Output)
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)
In principle (might need glasgow-exts), you could go ahead and declare instance Monad MSO where return = mkMSO (>>=) = bindMSO This doesn't work, because MSO ist just a function (the top type constructor is (->)), and there is already a Monad instance for (->). You could activate all sorts of extensions (glasgow-exts and overlapping-instances at the very least) to allow the overlap, but I guess, this will only serve to confuse first the type checker and later you. Instead, you have to make clear that MSO is represented as a function, but is to be treated as different, and that's what 'newtype' is for. After wrapping a function in a newtype, it is something else, so it has to be unwrapped before it can be used as a function again:
newtype MSO a = MSO { unMSO :: State -> (a, State, Output) }
mkMSO :: a -> MSO a mkMSO a = MSO (\s -> (a, s, ""))
bindMSO :: MSO a -> (a -> MSO b) -> MSO b bindMSO m f = MSO (\x -> let (a, y, s1) = unMSO m x in let (b, z, s2) = unMSO (f a) y in (b, z, s1 ++ s2))
and now MSO can no longer be confused with other functions and you can declare your Monad instance:
instance Monad MSO where return = mkMSO (>>=) = bindMSO
-- To be tested with: -- evalMSO (Add (Con 6) (Add (Con 16) (Add (Con 20) (Con 12)))) 0
Now this won't work, since evalMSO produces an MSO, not a function. You have to unwrap it to use the function:
unMSO (evalMSO (Add (Con 6) (Add (Con 16) (Add (Con 20) (Con 12))))) 0
Udo. -- From the MFC source: // according to the Win98 docs, this should be 1 // according to the WinNT docs, this should be 2 // they are both wrong!

Andrea Rossato wrote:
this is what I'm trying to do, sort of: turn the code at the button into the do-notation.[1]
module StateOutputMonad where
-- do notation only works with instances of Monad import Control.Monad
data Term = Con Int | Add Term Term deriving (Show)
type MSO a = State -> (a, State, Output)
-- Use a newtype so you can declare it as a Monad newtype MSO a = MSO (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
--The above 3 functions are replaced by an instance decl -- combineMSO (ie >>) is the same as the default method instance Monad MSO where return a = MSO (\s -> (a, s, "")) (MSO m) >>= f = MSO $ \x -> let (a, y, s1) = m x in let MSO y_bz = f a in let (b, z, s2) = y_bz y in (b, z, s1 ++ s2) -- Note the second let is needed to unwrap the newtype -- Also note you don't need 3 separate let constructs - you could -- just use one if you like
incMSOstate :: MSO () incMSOstate = \s -> ((), s + 1, "")
incMSOstate :: MSO () incMSOstate = MSO (\s -> ((), s + 1, ""))
outMSO :: Output -> MSO () outMSO = \x s -> ((),s, x)
-- We need to wrap the function returned by (outMSO x) as -- a value of (new)type MSO hence: outMSO :: Output -> MSO () outMSO x = MSO (\s -> ((),s, x)) -- You could also have written outMSO = \x -> MSO ... but it's -- preferable to put the x on the lhs to avoid the dreaded -- monomorphism restriction
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)
evalMSO :: Term -> MSO Int evalMSO (Con a) = do incMSOstate outMSO (formatLine (Con a) a) return a evalMSO (Add t u) = do a <- evalMSO t b <- evalMSO u incMSOstate outMSO (formatLine (Add t u) (a + b)) return (a + b)
-- To be tested with: -- evalMSO (Add (Con 6) (Add (Con 16) (Add (Con 20) (Con 12)))) 0
-- We need one more thing: a function to run the monad that's wrapped up -- inside the MSO newtype: runMSO :: MSO a -> State -> (a, State, Output) runMSO (MSO f) s = f s -- Tested with: -- runMSO (evalMSO (Add (Con 6) (Add (Con 16) (Add (Con 20) (Con 12))))) 0 Regards, Brian. -- Logic empowers us and Love gives us purpose. Yet still phantoms restless for eras long past, congealed in the present in unthought forms, strive mightily unseen to destroy us. http://www.metamilk.com

Il Sat, Aug 26, 2006 at 02:25:51PM +0100, Brian Hulley ebbe a scrivere:
runMSO :: MSO a -> State -> (a, State, Output) runMSO (MSO f) s = f s
this is exactly what I was looking for!!!! runMSO (MSO f) s = f s I've already done the previous part, but I was running it as: runMSO a = evalMSO a 0 and could not understand where the problem was! I though that the monad itself was wrong, and not that way I was running it!! sometimes I feel so stupid! the fact is that I was thinking that type MSO a = Int -> (a,Int,String) and MSO a = MSO (Int -> (a,Int,String) where the same stuff. I discovered the hard way that they are not, and it took me almost 2 days! Thanks a lot for your kind patience. Andrea

Il Sat, Aug 26, 2006 at 01:27:38AM +0200, Daniel Fischer ebbe a scrivere:
unT1 :: T1 a -> T a unT1 (T1 f) = f
makeT1 a b = unT1 (mkT1 a) b
will work fine.
*Prelude> :t makeT1 makeT1 :: a -> Int -> (a, Int) *Prelude> not that fine, though. Quite useless. try chancing to:
unT1 :: T1 a -> T1 a ^^^^ unT1 (T1 f) = f
All the best andrea
participants (6)
-
Andrea Rossato
-
Brian Hulley
-
Bulat Ziganshin
-
Daniel Fischer
-
Neil Mitchell
-
Udo Stenzel