Skip to content
Snippets Groups Projects
Commit b02188ab authored by Vladislav Zavialov's avatar Vladislav Zavialov Committed by sheaf
Browse files

Link to (~)

parent e057bfc8
No related branches found
No related tags found
5 merge requests!38Make --no-tmp-comp-dir the default,!37Adapt to latest xhtml version, various optimizations,!31Support HsToken in DataDecl and ClassDecl,!12Drop orphan instance when defined upstream.,!10Haddock interfaces produced from `.hi` files
{-# LANGUAGE BangPatterns, StandaloneDeriving, FlexibleInstances, ViewPatterns #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE ScopedTypeVariables #-}
......
{-# LANGUAGE CPP, DeriveDataTypeable, DeriveFunctor, DeriveFoldable, DeriveTraversable, StandaloneDeriving, TypeFamilies, RecordWildCards #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE PartialTypeSignatures #-}
......
......@@ -2,6 +2,7 @@
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE TypeSynonymInstances #-}
-- |
......
......@@ -230,7 +230,9 @@
><td class="src"
>:: <span class="keyword"
>forall</span
> a (b :: ()) d. d ~ '<a href="#" title="GHC.Tuple"
> a (b :: ()) d. d <a href="#" title="Data.Type.Equality"
>~</a
> '<a href="#" title="GHC.Tuple"
>()</a
></td
><td class="doc empty"
......
......@@ -147,7 +147,9 @@
><p class="src"
><a id="v:f" class="def"
>f</a
> :: a ~ b =&gt; a -&gt; b <a href="#" class="selflink"
> :: a <a href="#" title="Data.Type.Equality"
>~</a
> b =&gt; a -&gt; b <a href="#" class="selflink"
>#</a
></p
></div
......@@ -155,7 +157,11 @@
><p class="src"
><a id="v:g" class="def"
>g</a
> :: (a ~ b, b ~ c) =&gt; a -&gt; c <a href="#" class="selflink"
> :: (a <a href="#" title="Data.Type.Equality"
>~</a
> b, b <a href="#" title="Data.Type.Equality"
>~</a
> c) =&gt; a -&gt; c <a href="#" class="selflink"
>#</a
></p
></div
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment