Difference between revisions of "Scoped type variables"

From HaskellWiki
Jump to navigation Jump to search
m (ScopedTypeVariables moved to Scoped type variables)
(fix link to ghc user guide)
 
(6 intermediate revisions by 3 users not shown)
Line 1: Line 1:
Scoped Type Variables are an extension to Haskell's type system that allow free type variables to be re-used in the scope of a function. They are also described in the [http://www.haskell.org/ghc/docs/latest/html/users_guide/other-type-extensions.html#scoped-type-variables GHC documentation].
+
Scoped Type Variables are an extension to Haskell's type system that allow free type variables to be re-used in the scope of a function.
  +
  +
{{GHCUsersGuide|exts/scoped_type_variables||a Scoped Type Variables section}}
   
 
As an example, consider the following functions:
 
As an example, consider the following functions:
Line 27: Line 29:
 
</haskell>
 
</haskell>
   
Scoped type variables make it possible to specify the particular type of a function in situations where it is not otherwise possible, which can in turn help avoid problems with the [[Monomorphism_restriction]].
+
Scoped type variables make it possible to specify the particular type of a function in situations where it is not otherwise possible, which can in turn help avoid problems with the [[Monomorphism restriction]].
   
 
This feature should be better documented in the Wiki, but this is a start.
 
This feature should be better documented in the Wiki, but this is a start.
  +
  +
== Avoiding Scoped Type Variables ==
  +
  +
Although Scoped Type Variables are often a simple solution, they are not available in all compilers.
  +
Often there is a solution that is Haskell 98.
  +
First, there is
  +
<haskell>
  +
asTypeOf :: a -> a -> a
  +
asTypeOf a b = a
  +
.
  +
</haskell>
  +
It is used like <hask>x `asTypeOf` y</hask> and has the same value like <hask>x</hask>,
  +
but type inference asserts that <hask>x</hask> and <hask>y</hask> have the same type.
  +
  +
Sometimes it helps to divide a big function into smaller ones and give each of the small functions a signature.
  +
This also helps reading the program.
  +
  +
If this does not help, too, then use a helper function.
  +
E.g. if you want to determine the size of an object a pointer points to,
  +
then you might define a function like
  +
<haskell>
  +
sizeOfPtr :: Ptr a -> Int
  +
sizeOfPtr = sizeOf . (undefined :: Ptr a -> a)
  +
</haskell>
  +
<!-- provided by Lennart Augustsson in http://www.haskell.org/pipermail/haskell-cafe/2010-January/072060.html -->
  +
or
  +
<haskell>
  +
sizeOfPtr :: Ptr a -> a -> Int
  +
sizeOfPtr _ a = sizeOf a
  +
  +
sizeOf :: Ptr a -> Int
  +
sizeOf ptr = sizeOfPtr ptr undefined
  +
.
  +
</haskell>
  +
  +
== See also ==
  +
  +
* Haskell-Cafe on [http://www.haskell.org/pipermail/haskell-cafe/2009-December/071064.html sizeOf on a type]
  +
* Haskell-Cafe on [http://www.haskell.org/pipermail/haskell-cafe/2008-June/044617.html What is a rigid type variable?]
  +
* Haskell-Cafe on [http://www.haskell.org/pipermail/haskell-cafe/2008-April/042174.html asserting the type of a binding in a "do" expression]
   
 
[[Category:Glossary]]
 
[[Category:Glossary]]

Latest revision as of 22:56, 12 June 2021

Scoped Type Variables are an extension to Haskell's type system that allow free type variables to be re-used in the scope of a function.

The GHC Users Guide has a Scoped Type Variables section.

As an example, consider the following functions:

{-# LANGUAGE ScopedTypeVariables #-}

...

mkpair1 :: forall a b. a -> b -> (a,b)
mkpair1 aa bb = (ida aa, bb)
    where
      ida :: a -> a -- This refers to a in the function's type signature
      ida = id

mkpair2 :: forall a b. a -> b -> (a,b)
mkpair2 aa bb = (ida aa, bb)
    where
      ida :: b -> b -- Illegal, because refers to b in type signature
      ida = id

mkpair3 :: a -> b -> (a,b)
mkpair3 aa bb = (ida aa, bb)
    where
      ida :: b -> b -- Legal, because b is now a free variable
      ida = id

Scoped type variables make it possible to specify the particular type of a function in situations where it is not otherwise possible, which can in turn help avoid problems with the Monomorphism restriction.

This feature should be better documented in the Wiki, but this is a start.

Avoiding Scoped Type Variables

Although Scoped Type Variables are often a simple solution, they are not available in all compilers. Often there is a solution that is Haskell 98. First, there is

asTypeOf :: a -> a -> a
asTypeOf a b = a
.

It is used like x `asTypeOf` y and has the same value like x, but type inference asserts that x and y have the same type.

Sometimes it helps to divide a big function into smaller ones and give each of the small functions a signature. This also helps reading the program.

If this does not help, too, then use a helper function. E.g. if you want to determine the size of an object a pointer points to, then you might define a function like

sizeOfPtr :: Ptr a -> Int
sizeOfPtr = sizeOf . (undefined :: Ptr a -> a)

or

sizeOfPtr :: Ptr a -> a -> Int
sizeOfPtr _ a = sizeOf a

sizeOf :: Ptr a -> Int
sizeOf ptr = sizeOfPtr ptr undefined
.

See also