
Hi, I've recently had a discussion about type synonyms and when to use them in haskell. On the one hand, they make reading type signatures easier and tell you what is meant, not just what is inside. On the other hand they also sort of hide what is inside, although you will probably need to know exactly that when using them. This might make reading code for new collaborators more difficult if they have to memorize all type synonyms first. So there are basically a few questions: * What do you think is a good policy for when and how to use them? Or would you say just not use them at all and put equivalent information in parameter documentation? * What are the upsides, downsides, pitfalls and also alternatives? (for completeness, also since https://www.haskell.org/haskellwiki/Type_synonym is a bit sparse) * Can we do something to improve the downsides? Or is there already something? (e.g. editor/IDE that can tell me the underlying type, error messages etc.) -- Regards, Julian Ospald

I tend to reserve type synonyms exclusively for *abbreviating* types,
for example when they end up being long and unwieldy. Since this is
seldom necessary, I seldom use type synonyms. Others (ab?)use type
synonyms to convey semantic information, e.g.
type Age = Int
However, if the need for naming things separately at the type level
really is pressing, then one could argue that for that you would be
better served introducing a newtype anyways.
IOW, my rule of thumb is: type synonyms only as abbreviations,
newtypes for semantically distinct entities, neither when the overhead
of a newtype wouldn't pay its own way in terms of either static
checking or clarity.
Best,
Mathieu
On 17 January 2015 at 20:06, Julian Ospald
Hi,
I've recently had a discussion about type synonyms and when to use them in haskell.
On the one hand, they make reading type signatures easier and tell you what is meant, not just what is inside. On the other hand they also sort of hide what is inside, although you will probably need to know exactly that when using them. This might make reading code for new collaborators more difficult if they have to memorize all type synonyms first.
So there are basically a few questions: * What do you think is a good policy for when and how to use them? Or would you say just not use them at all and put equivalent information in parameter documentation? * What are the upsides, downsides, pitfalls and also alternatives? (for completeness, also since https://www.haskell.org/haskellwiki/Type_synonym is a bit sparse) * Can we do something to improve the downsides? Or is there already something? (e.g. editor/IDE that can tell me the underlying type, error messages etc.)
-- Regards, Julian Ospald _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Projects written in an imperative style are the ones where type synonyms
can really help. For example, some gtk functions have horrible type
declarations, like
adjustmentNew :: Double -> Double -> Double -> Double -> Double -> Double
-> IO Adjustment
Gtk was designed for an imperative setting, and as such should provide type
synonyms to make users more comfortable.
In a purely functional style type synonyms are not as necessary. Most
functions are self-descriptive, e.g. a function operating on age would make
it obvious that it's operating on age, like,
incrementAge :: Int -> Int
You can argue that this declaration is more informative, as it doesn't hide
the details of 'Age' but yet doesn't confuse the reader.
As for help provided by the editor, I use emacs-haskell-mode, and it
provides interactions with an inferior ghc process. It allows you to query
the type and then see the result at the bottom of the window.
On 18 January 2015 at 01:37, Mathieu Boespflug
I tend to reserve type synonyms exclusively for *abbreviating* types, for example when they end up being long and unwieldy. Since this is seldom necessary, I seldom use type synonyms. Others (ab?)use type synonyms to convey semantic information, e.g.
type Age = Int
However, if the need for naming things separately at the type level really is pressing, then one could argue that for that you would be better served introducing a newtype anyways.
IOW, my rule of thumb is: type synonyms only as abbreviations, newtypes for semantically distinct entities, neither when the overhead of a newtype wouldn't pay its own way in terms of either static checking or clarity.
Best,
Mathieu
On 17 January 2015 at 20:06, Julian Ospald
wrote: Hi,
I've recently had a discussion about type synonyms and when to use them in haskell.
On the one hand, they make reading type signatures easier and tell you what is meant, not just what is inside. On the other hand they also sort of hide what is inside, although you will probably need to know exactly that when using them. This might make reading code for new collaborators more difficult if they have to memorize all type synonyms first.
So there are basically a few questions: * What do you think is a good policy for when and how to use them? Or would you say just not use them at all and put equivalent information in parameter documentation? * What are the upsides, downsides, pitfalls and also alternatives? (for completeness, also since https://www.haskell.org/haskellwiki/Type_synonym is a bit sparse) * Can we do something to improve the downsides? Or is there already something? (e.g. editor/IDE that can tell me the underlying type, error messages etc.)
-- Regards, Julian Ospald _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Regards Sumit Sahrawat

In the land of Haskell Web Development, I tend to use newtypes instead of
types. In works well in that domain because we often use the types opaquely
anyway. For example, I might have a bunch of values like UserId, PageId,
etc, which are really just an Int(eger) underneath. Preventing them from
being mixed up is good. Also, I am not doing any calculations on them --
just storing, retrieving, and passing them around. Additionally, I am not
usually creating the values directly in my code. That is, I don't have a
bunch of code like, getUser (UserId 4). It is more like, do uid <-
getUserId ; user <- getUser uid. So newtypes are great in this domain.
Outside of webdev, it is tempting to use type aliases for functions that
have a lot of types where the meaning is not clear:
foo :: Int -> Int -> Double -> Double -> Double -> IO ()
using type alias provides a way to give them meaning:
foo :: X -> Y -> Red -> Blue -> Green -> IO ()
but, that is confusing because it hides the underlying types. It also
duplicates information that is available in the function declaration.
foo :: Int -> Int -> Double -> Double -> Double -> IO ()
foo x y r g b = ...
Now we see types and description names. Except haddock does not include a
way to show the names of the arguments in the docs.
Obviously, we need dependent types:
foo : (x : Int) -> (y : Int) -> (red : Double) -> (blue : Double) -> (green
: Double) -> IO ()
And that will solve everything! What could possibly go wrong!
- jeremy
On Sat, Jan 17, 2015 at 1:06 PM, Julian Ospald
Hi,
I've recently had a discussion about type synonyms and when to use them in haskell.
On the one hand, they make reading type signatures easier and tell you what is meant, not just what is inside. On the other hand they also sort of hide what is inside, although you will probably need to know exactly that when using them. This might make reading code for new collaborators more difficult if they have to memorize all type synonyms first.
So there are basically a few questions: * What do you think is a good policy for when and how to use them? Or would you say just not use them at all and put equivalent information in parameter documentation? * What are the upsides, downsides, pitfalls and also alternatives? (for completeness, also since https://www.haskell.org/haskellwiki/Type_synonym is a bit sparse) * Can we do something to improve the downsides? Or is there already something? (e.g. editor/IDE that can tell me the underlying type, error messages etc.)
-- Regards, Julian Ospald _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

foo : (x : Int) -> (y : Int) -> (red : Double) -> (blue : Double) -> (green : Double) -> IO ()
And that will solve everything! What could possibly go wrong!
How about a type-level the? =p type The label t = t foo :: The red Double -> The green Double -> The blue Double -> IO () Or with polykinds: foo :: The "Red" Double -> The "Green" Double -> The "Blue" Double -> IO ()

On Mon, 19 Jan 2015 01:12:58 +0100, Christopher Done
foo : (x : Int) -> (y : Int) -> (red : Double) -> (blue : Double) -> (green : Double) -> IO ()
And that will solve everything! What could possibly go wrong!
How about a type-level the? =p
type The label t = t
foo :: The red Double -> The green Double -> The blue Double -> IO ()
Or with polykinds:
foo :: The "Red" Double -> The "Green" Double -> The "Blue" Double -> IO ()
Clearly needs more TypeOperators. type (l ∷ t) = t foo :: ("red" ∷ Double) -> ("green" ∷ Double) -> ("blue" ∷ Double) -> IO ()

Now we're definitely getting somewhere! I'm not to thrilled about the use
of string literals though. How about this?
{-# LANGUAGE TypeOperators, DataKinds, RankNTypes #-}
type (l ∷ t) = t
foo :: forall red green blue. (red ∷ Double) -> (green ∷ Double) -> (blue ∷
Double) -> IO ()
We just need to patch hlint to make this the suggested style.
- jeremy
On Sun, Jan 18, 2015 at 7:05 PM, Niklas Haas
On Mon, 19 Jan 2015 01:12:58 +0100, Christopher Done
wrote: foo : (x : Int) -> (y : Int) -> (red : Double) -> (blue : Double) -> (green : Double) -> IO ()
And that will solve everything! What could possibly go wrong!
How about a type-level the? =p
type The label t = t
foo :: The red Double -> The green Double -> The blue Double -> IO ()
Or with polykinds:
foo :: The "Red" Double -> The "Green" Double -> The "Blue" Double -> IO ()
Clearly needs more TypeOperators.
type (l ∷ t) = t
foo :: ("red" ∷ Double) -> ("green" ∷ Double) -> ("blue" ∷ Double) -> IO () _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Now we're definitely getting somewhere! I'm not to thrilled about the use of string literals though. How about this?
{-# LANGUAGE TypeOperators, DataKinds, RankNTypes #-} type (l ∷ t) = t
foo :: forall red green blue. (red ∷ Double) -> (green ∷ Double) -> (blue ∷ Double) -> IO ()
We just need to patch hlint to make this the suggested style.
- jeremy
In fact, why even bother with the explicit forall? Default behavior is to universally quantify unused variable names, after all. {-# LANGUAGE TypeOperators #-} type (l ∷ t) = t foo :: (red ∷ Double) -> (green ∷ Double) -> (blue ∷ Double) -> IO () At this point, I think this is a syntax form we can surely all agree upon.

That's pretty but a pain to type.
On 21 January 2015 at 16:32, Niklas Haas
Now we're definitely getting somewhere! I'm not to thrilled about the use of string literals though. How about this?
{-# LANGUAGE TypeOperators, DataKinds, RankNTypes #-} type (l ∷ t) = t
foo :: forall red green blue. (red ∷ Double) -> (green ∷ Double) -> (blue ∷ Double) -> IO ()
We just need to patch hlint to make this the suggested style.
- jeremy
In fact, why even bother with the explicit forall? Default behavior is to universally quantify unused variable names, after all.
{-# LANGUAGE TypeOperators #-}
type (l ∷ t) = t
foo :: (red ∷ Double) -> (green ∷ Double) -> (blue ∷ Double) -> IO ()
At this point, I think this is a syntax form we can surely all agree upon. _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Considering it doesnt give you any type safety, why not just write:
foo (red :: Double) (green :: Double) (blue :: Double) = undefined
Tom
El Jan 21, 2015, a las 10:32, Niklas Haas
Now we're definitely getting somewhere! I'm not to thrilled about the use of string literals though. How about this?
{-# LANGUAGE TypeOperators, DataKinds, RankNTypes #-} type (l ∷ t) = t
foo :: forall red green blue. (red ∷ Double) -> (green ∷ Double) -> (blue ∷ Double) -> IO ()
We just need to patch hlint to make this the suggested style.
- jeremy
In fact, why even bother with the explicit forall? Default behavior is to universally quantify unused variable names, after all.
{-# LANGUAGE TypeOperators #-}
type (l ∷ t) = t
foo :: (red ∷ Double) -> (green ∷ Double) -> (blue ∷ Double) -> IO ()
At this point, I think this is a syntax form we can surely all agree upon. _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Because that wouldn't show up in haddock or :t.
On 22 January 2015 at 01:23,
Considering it doesnt give you any type safety, why not just write:
foo (red :: Double) (green :: Double) (blue :: Double) = undefined
Tom
El Jan 21, 2015, a las 10:32, Niklas Haas
escribió: Now we're definitely getting somewhere! I'm not to thrilled about the use of string literals though. How about this?
{-# LANGUAGE TypeOperators, DataKinds, RankNTypes #-} type (l ∷ t) = t
foo :: forall red green blue. (red ∷ Double) -> (green ∷ Double) -> (blue ∷ Double) -> IO ()
We just need to patch hlint to make this the suggested style.
- jeremy
In fact, why even bother with the explicit forall? Default behavior is to universally quantify unused variable names, after all.
{-# LANGUAGE TypeOperators #-}
type (l ∷ t) = t
foo :: (red ∷ Double) -> (green ∷ Double) -> (blue ∷ Double) -> IO ()
At this point, I think this is a syntax form we can surely all agree upon. _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Clearly needs more TypeOperators.
type (l ∷ t) = t
foo :: ("red" ∷ Double) -> ("green" ∷ Double) -> ("blue" ∷ Double) -> IO ()
That looks similar to an earlier proposal: https://www.haskell.org/pipermail/haskell-cafe/2012-December/105494.html which doesn't seem to have caught on.

I personally really dislike type synonyms, 9 times out of 10 I would prefer
to just read a full type than the obscured synonym which hides useful
structure from me.
On 17 January 2015 at 20:06, Julian Ospald
Hi,
I've recently had a discussion about type synonyms and when to use them in haskell.
On the one hand, they make reading type signatures easier and tell you what is meant, not just what is inside. On the other hand they also sort of hide what is inside, although you will probably need to know exactly that when using them. This might make reading code for new collaborators more difficult if they have to memorize all type synonyms first.
So there are basically a few questions: * What do you think is a good policy for when and how to use them? Or would you say just not use them at all and put equivalent information in parameter documentation? * What are the upsides, downsides, pitfalls and also alternatives? (for completeness, also since https://www.haskell.org/haskellwiki/Type_synonym is a bit sparse) * Can we do something to improve the downsides? Or is there already something? (e.g. editor/IDE that can tell me the underlying type, error messages etc.)
-- Regards, Julian Ospald _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Sun, Jan 18, 2015 at 7:02 PM, Christopher Done
I personally really dislike type synonyms, 9 times out of 10 I would prefer to just read a full type than the obscured synonym which hides useful structure from me.
I'm actually inclined to agree with this; the examples where they are intended to clarify an API strike me as places where said API would likely benefit from using actual types anyway so you don't mix things that shouldn't be mixed. (In my experience, most of those are FFI imports or thin wrappers over same, and a higher level Haskelly interface built on top is a better answer than weird synonyms. On the other hand, internal type synonyms to help the author of such an interface keep the FFI parameters straight likely make sense; sadly, there's no way to fix C....) -- brandon s allbery kf8nh sine nomine associates allbery.b@gmail.com ballbery@sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net

On 19/01/2015 01:02, Christopher Done wrote:
I personally really dislike type synonyms, 9 times out of 10 I would prefer to just read a full type than the obscured synonym which hides useful structure from me.
i find type synonyms mostly useful during prototyping, i.e. when what I want is actually a newtype for safer interfaces but I don't want to bother with wrapping/unwrapping or figuring out how to derive instances; this is especially true for monad transformer stacks. later, after the code has settled a bit, it's straight forward, if tedious, to change the type to a newtype and fix the resulting type errors. sk

I agree with Stefan -- type synonyms are really useful in developing
project by yourself (or a small team), where you are the one both using and
generating the synonyms, and no-one else needs to care. Then, the simple
Age = Int is still very meaningful for yourself in both documenting and
directing the writing.
But in a public library, finding out that a type X is actually 'Either z'
kind of blocks the way -- you don't know how to operate with X until you
become to know what it really is.. And then you have to memorize this for
the future to stay productive, which is not very easy if there are many
libraries that you're using. (But on the other hand if X equals something
else and more complex, that you don't know, then the synonym I think
becomes more useful again.)
On Mon, Jan 19, 2015 at 11:16 AM, Stefan Kersten
On 19/01/2015 01:02, Christopher Done wrote:
I personally really dislike type synonyms, 9 times out of 10 I would prefer to just read a full type than the obscured synonym which hides useful structure from me.
i find type synonyms mostly useful during prototyping, i.e. when what I want is actually a newtype for safer interfaces but I don't want to bother with wrapping/unwrapping or figuring out how to derive instances; this is especially true for monad transformer stacks. later, after the code has settled a bit, it's straight forward, if tedious, to change the type to a newtype and fix the resulting type errors.
sk _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Carl Eyeinsky

But in a public library, finding out that a type X is actually 'Either z' kind of blocks the way
It does. It's quite annoying to have to jump through several layers of indirections especially since (currently) Haddock-generated documentation requires you to click through the link to see what it's aliased to (a mouseover tooltip would be really nice to have!). I would rather just document each parameter using the `-- ^` syntax.

I think they have their place. I use them when it's too much bother
to unwrap a newtype but still nice to have some documentation,
especially if it shows up in many places but I only want to document
in one place. Or if I think a type error is unlikely, or not a big
deal, compared to the wrap/unwrap hassle. For documentation it's also
nice to have a name to use in haddock. Also I tend to use them when
the scope is small. I agree that if the scope is wide, or if it's a
library, then they can be not worth it. E.g. I've decided to not use
Data.Graph's 'type Forest a = [Tree a]'.
It's a convenience vs. correctness trade-off, and it's useful to have
something covering the convenience end. Perhaps you shouldn't put
them in library APIs though.
On Sun, Jan 18, 2015 at 3:06 AM, Julian Ospald
Hi,
I've recently had a discussion about type synonyms and when to use them in haskell.
On the one hand, they make reading type signatures easier and tell you what is meant, not just what is inside. On the other hand they also sort of hide what is inside, although you will probably need to know exactly that when using them. This might make reading code for new collaborators more difficult if they have to memorize all type synonyms first.
So there are basically a few questions: * What do you think is a good policy for when and how to use them? Or would you say just not use them at all and put equivalent information in parameter documentation? * What are the upsides, downsides, pitfalls and also alternatives? (for completeness, also since https://www.haskell.org/haskellwiki/Type_synonym is a bit sparse) * Can we do something to improve the downsides? Or is there already something? (e.g. editor/IDE that can tell me the underlying type, error messages etc.)
-- Regards, Julian Ospald _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

In general, use newtypes instead of type synonyms, and records instead of tuples. Also, ghc has its flaws when dealing with type synonyms, i.e., in error messages you find a type synoym needlessly expanded. Does anyone know a programming language that has type synonyms and always uses the type syn. in error messages when the user originally wrote it? I'd be eager to learn. Cheers, Andreas On 19.01.2015 12:15, Evan Laforge wrote:
I think they have their place. I use them when it's too much bother to unwrap a newtype but still nice to have some documentation, especially if it shows up in many places but I only want to document in one place. Or if I think a type error is unlikely, or not a big deal, compared to the wrap/unwrap hassle. For documentation it's also nice to have a name to use in haddock. Also I tend to use them when the scope is small. I agree that if the scope is wide, or if it's a library, then they can be not worth it. E.g. I've decided to not use Data.Graph's 'type Forest a = [Tree a]'.
It's a convenience vs. correctness trade-off, and it's useful to have something covering the convenience end. Perhaps you shouldn't put them in library APIs though.
On Sun, Jan 18, 2015 at 3:06 AM, Julian Ospald
wrote: Hi,
I've recently had a discussion about type synonyms and when to use them in haskell.
On the one hand, they make reading type signatures easier and tell you what is meant, not just what is inside. On the other hand they also sort of hide what is inside, although you will probably need to know exactly that when using them. This might make reading code for new collaborators more difficult if they have to memorize all type synonyms first.
So there are basically a few questions: * What do you think is a good policy for when and how to use them? Or would you say just not use them at all and put equivalent information in parameter documentation? * What are the upsides, downsides, pitfalls and also alternatives? (for completeness, also since https://www.haskell.org/haskellwiki/Type_synonym is a bit sparse) * Can we do something to improve the downsides? Or is there already something? (e.g. editor/IDE that can tell me the underlying type, error messages etc.)
-- Regards, Julian Ospald _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Andreas Abel <>< Du bist der geliebte Mensch. Department of Computer Science and Engineering Chalmers and Gothenburg University, Sweden andreas.abel@gu.se http://www2.tcs.ifi.lmu.de/~abel/
participants (14)
-
adam vogt
-
amindfv@gmail.com
-
Andreas Abel
-
Brandon Allbery
-
Carl Eyeinsky
-
Christopher Done
-
Evan Laforge
-
Jeremy Shaw
-
Julian Ospald
-
Mathieu Boespflug
-
Niklas Haas
-
Phil Ruffwind
-
Stefan Kersten
-
Sumit Sahrawat, Maths & Computing, IIT (BHU)