From 32eaf3a13f22ff4ecbce395874e2a86f96a96782 Mon Sep 17 00:00:00 2001 From: David Waern Date: Mon, 6 Dec 2010 14:09:18 +0000 Subject: Update tests following recent changes --- tests/golden-tests/tests/A.html.ref | 2 +- tests/golden-tests/tests/B.html.ref | 2 +- tests/golden-tests/tests/Bug1.html.ref | 2 +- tests/golden-tests/tests/Bug2.html.ref | 2 +- tests/golden-tests/tests/Bug3.html.ref | 2 +- tests/golden-tests/tests/Bug4.html.ref | 2 +- tests/golden-tests/tests/Bug6.html.ref | 2 +- tests/golden-tests/tests/Bug7.html.ref | 2 +- tests/golden-tests/tests/Bug8.html.ref | 2 +- tests/golden-tests/tests/Bugs.html.ref | 2 +- tests/golden-tests/tests/CrossPackageDocs.html.ref | 20 ++++++++--------- tests/golden-tests/tests/Examples.html.ref | 2 +- tests/golden-tests/tests/FunArgs.html.ref | 2 +- tests/golden-tests/tests/GADTRecords.html.ref | 2 +- tests/golden-tests/tests/Hash.html.ref | 8 +++---- tests/golden-tests/tests/NamedDoc.html.ref | 2 +- tests/golden-tests/tests/NoLayout.html.ref | 2 +- tests/golden-tests/tests/QuasiExpr.html.ref | 2 +- tests/golden-tests/tests/QuasiQuote.html.ref | 2 +- tests/golden-tests/tests/TH.html.ref | 2 +- tests/golden-tests/tests/TH2.html.ref | 2 +- tests/golden-tests/tests/Test.html.ref | 26 +++++++++++----------- tests/golden-tests/tests/Ticket112.html.ref | 2 +- tests/golden-tests/tests/Ticket61.html.ref | 2 +- tests/golden-tests/tests/Ticket75.html.ref | 2 +- tests/golden-tests/tests/TypeFamilies.html.ref | 2 +- tests/golden-tests/tests/TypeOperators.html.ref | 4 ++-- tests/golden-tests/tests/Visible.html.ref | 2 +- 28 files changed, 53 insertions(+), 53 deletions(-) (limited to 'tests/golden-tests') diff --git a/tests/golden-tests/tests/A.html.ref b/tests/golden-tests/tests/A.html.ref index 81d2029a..495b264b 100644 --- a/tests/golden-tests/tests/A.html.ref +++ b/tests/golden-tests/tests/A.html.ref @@ -1,4 +1,4 @@ A

 

A

Documentation

data A

Constructors

A 
\ No newline at end of file +

 

A

Documentation

data A

Constructors

A 
\ No newline at end of file diff --git a/tests/golden-tests/tests/B.html.ref b/tests/golden-tests/tests/B.html.ref index 3de4cb57..c1bcfe23 100644 --- a/tests/golden-tests/tests/B.html.ref +++ b/tests/golden-tests/tests/B.html.ref @@ -1,4 +1,4 @@ B

 

B

Documentation

module A

\ No newline at end of file +

 

B

Documentation

module A

\ No newline at end of file diff --git a/tests/golden-tests/tests/Bug1.html.ref b/tests/golden-tests/tests/Bug1.html.ref index 2580a9a8..3ea9f6ff 100644 --- a/tests/golden-tests/tests/Bug1.html.ref +++ b/tests/golden-tests/tests/Bug1.html.ref @@ -3,4 +3,4 @@ window.onload = function () {pageLoad();setSynopsis("mini_Bug1.html");}; //]]>

 

Bug1

Synopsis

  • data T = T

Documentation

data T

We should have different anchors for constructors and types/classes. This hyperlink should point to the type constructor by default: T. -

Constructors

T 
\ No newline at end of file +

Constructors

T 
\ No newline at end of file diff --git a/tests/golden-tests/tests/Bug2.html.ref b/tests/golden-tests/tests/Bug2.html.ref index bc8acefb..09b01947 100644 --- a/tests/golden-tests/tests/Bug2.html.ref +++ b/tests/golden-tests/tests/Bug2.html.ref @@ -1,4 +1,4 @@ Bug2

 

Bug2

Documentation

x :: A

\ No newline at end of file +

 

Bug2

Documentation

x :: A

\ No newline at end of file diff --git a/tests/golden-tests/tests/Bug3.html.ref b/tests/golden-tests/tests/Bug3.html.ref index 78814b68..4edfe76e 100644 --- a/tests/golden-tests/tests/Bug3.html.ref +++ b/tests/golden-tests/tests/Bug3.html.ref @@ -3,4 +3,4 @@ window.onload = function () {pageLoad();setSynopsis("mini_Bug3.html");}; //]]>

 

Bug3

Synopsis

Documentation

foo :: Int

/multi-line emphasis/ -

\ No newline at end of file +

\ No newline at end of file diff --git a/tests/golden-tests/tests/Bug4.html.ref b/tests/golden-tests/tests/Bug4.html.ref index ae7b62d5..76b0e84f 100644 --- a/tests/golden-tests/tests/Bug4.html.ref +++ b/tests/golden-tests/tests/Bug4.html.ref @@ -2,4 +2,4 @@ window.onload = function () {pageLoad();setSynopsis("mini_Bug4.html");}; //]]>

 

Bug4

Synopsis

Documentation

foo :: Int

don't use apostrophe's in the wrong place's -

\ No newline at end of file +

\ No newline at end of file diff --git a/tests/golden-tests/tests/Bug6.html.ref b/tests/golden-tests/tests/Bug6.html.ref index 697390a2..6bc8ca26 100644 --- a/tests/golden-tests/tests/Bug6.html.ref +++ b/tests/golden-tests/tests/Bug6.html.ref @@ -9,4 +9,4 @@ window.onload = function () {pageLoad();setSynopsis("mini_Bug6.html");};

Constructors

C 

Fields

c1 :: Int
 
c2 :: Int
 

data D

.. with only some of the fields exported (we can't handle this one - how do we render the declaration?)

Constructors

D Int Int 

newtype E

a newtype with a field -

Constructors

E Int 
\ No newline at end of file +

Constructors

E Int 
\ No newline at end of file diff --git a/tests/golden-tests/tests/Bug7.html.ref b/tests/golden-tests/tests/Bug7.html.ref index 10e06791..6c29ce13 100644 --- a/tests/golden-tests/tests/Bug7.html.ref +++ b/tests/golden-tests/tests/Bug7.html.ref @@ -7,4 +7,4 @@ window.onload = function () {pageLoad();setSynopsis("mini_Bug7.html");};

Constructors

Foo 

Instances

Bar Foo Foo

Just one instance

class Bar x y

The Bar class

Instances

Bar Foo Foo

Just one instance -

\ No newline at end of file +

\ No newline at end of file diff --git a/tests/golden-tests/tests/Bug8.html.ref b/tests/golden-tests/tests/Bug8.html.ref index 24ec29f6..bd2dc3d1 100644 --- a/tests/golden-tests/tests/Bug8.html.ref +++ b/tests/golden-tests/tests/Bug8.html.ref @@ -1,4 +1,4 @@ Bug8

 

Bug8

Documentation

data Typ

Constructors

Type (String, [Typ]) 
TFree (String, [String]) 
\ No newline at end of file +

 

Bug8

Documentation

data Typ

Constructors

Type (String, [Typ]) 
TFree (String, [String]) 
\ No newline at end of file diff --git a/tests/golden-tests/tests/Bugs.html.ref b/tests/golden-tests/tests/Bugs.html.ref index 3c9fce9e..6595502a 100644 --- a/tests/golden-tests/tests/Bugs.html.ref +++ b/tests/golden-tests/tests/Bugs.html.ref @@ -1,4 +1,4 @@ Bugs

 

Bugs

Documentation

data A a

Constructors

A a (a -> Int) 
\ No newline at end of file +

 

Bugs

Documentation

data A a

Constructors

A a (a -> Int) 
\ No newline at end of file diff --git a/tests/golden-tests/tests/CrossPackageDocs.html.ref b/tests/golden-tests/tests/CrossPackageDocs.html.ref index c7854745..a3c5a424 100644 --- a/tests/golden-tests/tests/CrossPackageDocs.html.ref +++ b/tests/golden-tests/tests/CrossPackageDocs.html.ref @@ -3,9 +3,9 @@ window.onload = function () {pageLoad();setSynopsis("mini_CrossPackageDocs.html" //]]>

 

CrossPackageDocs

Synopsis

Documentation

map :: (a -> b) -> [a] -> [b]

map f xs is the list obtained by applying f to each element of xs, i.e., -

map f [x1, x2, ..., xn] == [f x1, f x2, ..., f xn] +

 map f [x1, x2, ..., xn] == [f x1, f x2, ..., f xn]
  map f [x1, x2, ...] == [f x1, f x2, ...]
-

class Monad m where

The Monad class defines the basic operations over a monad, +

class Monad m where

The Monad class defines the basic operations over a monad, a concept from a branch of mathematics known as category theory. From the perspective of a Haskell programmer, however, it is best to think of a monad as an abstract datatype of actions. @@ -13,12 +13,12 @@ Haskell's do expressions provide a convenient syntax for writing monadic expressions.

Minimal complete definition: >>= and return.

Instances of Monad should satisfy the following laws: -

return a >>= k == k a +

 return a >>= k  ==  k a
  m >>= return  ==  m
  m >>= (\x -> k x >>= h)  ==  (m >>= k) >>= h
-

Instances of both Monad and Functor should additionally satisfy the law: -

fmap f xs == xs >>= return . f -

The instances of Monad for lists, Data.Maybe.Maybe and System.IO.IO +

Instances of both Monad and Functor should additionally satisfy the law: +

 fmap f xs  ==  xs >>= return . f
+

The instances of Monad for lists, Data.Maybe.Maybe and System.IO.IO defined in the Prelude satisfy these laws.

Methods

(>>=) :: m a -> (a -> m b) -> m b

Sequentially compose two actions, passing any value produced by the first as an argument to the second. @@ -29,15 +29,15 @@ defined in the Prelude satisfy these laws.

fail :: String -> m a

Fail with a message. This operation is not part of the mathematical definition of a monad, but is invoked on pattern-match failure in a do expression. -

Instances

Monad [] 
Monad IO 
Monad Q 
Monad Maybe 
Monad ((->) r) 

runInteractiveProcess

Arguments

:: FilePath

Filename of the executable +

Instances

Monad [] 
Monad IO 
Monad Q 
Monad Maybe 
Monad ((->) r) 
Monad (Either e) 

runInteractiveProcess

Arguments

:: FilePath

Filename of the executable

-> [String]

Arguments to pass to the executable

-> Maybe FilePath

Optional path to the working directory

-> Maybe [(String, String)]

Optional environment (otherwise inherit)

-> IO (Handle, Handle, Handle, ProcessHandle) 

Runs a raw command, and returns Handles that may be used to communicate with the process via its stdin, stdout and stderr respectively.

For example, to start a process and feed a string to its stdin: -

(inp,out,err,pid) <- runInteractiveProcess "..." +

   (inp,out,err,pid) <- runInteractiveProcess "..."
    forkIO (hPutStr inp str)
-

The Handles are initially in binary mode; if you need them to be +

The Handles are initially in binary mode; if you need them to be in text mode then use hSetBinaryMode. -

\ No newline at end of file +

\ No newline at end of file diff --git a/tests/golden-tests/tests/Examples.html.ref b/tests/golden-tests/tests/Examples.html.ref index 3bf475ab..a8f63e3e 100644 --- a/tests/golden-tests/tests/Examples.html.ref +++ b/tests/golden-tests/tests/Examples.html.ref @@ -19,4 +19,4 @@ window.onload = function () {pageLoad();setSynopsis("mini_Examples.html");};

>>> import Data.Char
 >>> isSpace 'a'
 False
-
\ No newline at end of file + \ No newline at end of file diff --git a/tests/golden-tests/tests/FunArgs.html.ref b/tests/golden-tests/tests/FunArgs.html.ref index 57c903de..1491b267 100644 --- a/tests/golden-tests/tests/FunArgs.html.ref +++ b/tests/golden-tests/tests/FunArgs.html.ref @@ -10,4 +10,4 @@ window.onload = function () {pageLoad();setSynopsis("mini_FunArgs.html");};

-> b

Second argument

-> c

Third argument

-> d

Result -

\ No newline at end of file +

\ No newline at end of file diff --git a/tests/golden-tests/tests/GADTRecords.html.ref b/tests/golden-tests/tests/GADTRecords.html.ref index 6a5743fb..f4d5593b 100644 --- a/tests/golden-tests/tests/GADTRecords.html.ref +++ b/tests/golden-tests/tests/GADTRecords.html.ref @@ -4,4 +4,4 @@ window.onload = function () {pageLoad();setSynopsis("mini_GADTRecords.html");};

 

GADTRecords

Synopsis

Documentation

data H1 a b where

h1

Constructors

C1 :: H1 a b 
C2 :: Ord a => [a] -> H1 a a 
C3 :: Int -> H1 Int Int 

Fields

field :: Int

hello docs

C4 :: a -> H1 Int a 

Fields

field2 :: a

hello2 docs -

\ No newline at end of file +

\ No newline at end of file diff --git a/tests/golden-tests/tests/Hash.html.ref b/tests/golden-tests/tests/Hash.html.ref index 50eef343..b4fa23f7 100644 --- a/tests/golden-tests/tests/Hash.html.ref +++ b/tests/golden-tests/tests/Hash.html.ref @@ -6,15 +6,15 @@ window.onload = function () {pageLoad();setSynopsis("mini_Hash.html");};
  • The Hash class
  • Description

    Implementation of fixed-size hash tables, with a type class for constructing hash values for structured types. -

    Synopsis

    The HashTable type +

    Synopsis

    The HashTable type

    data HashTable key val

    A hash table with keys of type key and values of type val. The type key should be an instance of Eq. -

    Operations on HashTables +

    Operations on HashTables

    new :: (Eq key, Hash key) => Int -> IO (HashTable key val)

    Builds a new hash table with a given size

    insert :: (Eq key, Hash key) => key -> val -> IO ()

    Inserts a new element into the hash table

    lookup :: Hash key => key -> IO (Maybe val)

    Looks up a key in the hash table, returns Just val if the key was found, or Nothing otherwise. -

    The Hash class +

    The Hash class

    class Hash a where

    A class of types which can be hashed.

    Methods

    hash :: a -> Int

    hashes the value of type a into an Int -

    Instances

    Hash Float 
    Hash Int 
    (Hash a, Hash b) => Hash (a, b) 
    \ No newline at end of file +

    Instances

    Hash Float 
    Hash Int 
    (Hash a, Hash b) => Hash (a, b) 
    \ No newline at end of file diff --git a/tests/golden-tests/tests/NamedDoc.html.ref b/tests/golden-tests/tests/NamedDoc.html.ref index b2587392..25cdc423 100644 --- a/tests/golden-tests/tests/NamedDoc.html.ref +++ b/tests/golden-tests/tests/NamedDoc.html.ref @@ -2,4 +2,4 @@ window.onload = function () {pageLoad();setSynopsis("mini_NamedDoc.html");}; //]]>

     

    NamedDoc

    Synopsis

      Documentation

      bar -

      \ No newline at end of file +

      \ No newline at end of file diff --git a/tests/golden-tests/tests/NoLayout.html.ref b/tests/golden-tests/tests/NoLayout.html.ref index 1dc76b79..aa1fd3b9 100644 --- a/tests/golden-tests/tests/NoLayout.html.ref +++ b/tests/golden-tests/tests/NoLayout.html.ref @@ -2,4 +2,4 @@ window.onload = function () {pageLoad();setSynopsis("mini_NoLayout.html");}; //]]>

       

      NoLayout

      Synopsis

      Documentation

      g :: Int

      the function g -

      \ No newline at end of file +

      \ No newline at end of file diff --git a/tests/golden-tests/tests/QuasiExpr.html.ref b/tests/golden-tests/tests/QuasiExpr.html.ref index 0f0d00f9..30735270 100644 --- a/tests/golden-tests/tests/QuasiExpr.html.ref +++ b/tests/golden-tests/tests/QuasiExpr.html.ref @@ -1,4 +1,4 @@ QuasiExpr

       

      QuasiExpr

      Documentation

      data BinOp

      Constructors

      AddOp 
      SubOp 
      MulOp 
      DivOp 

      parseExprExp :: String -> Q Exp

      \ No newline at end of file +

       

      QuasiExpr

      Documentation

      data BinOp

      Constructors

      AddOp 
      SubOp 
      MulOp 
      DivOp 

      Instances

      parseExprExp :: String -> Q Exp

      \ No newline at end of file diff --git a/tests/golden-tests/tests/QuasiQuote.html.ref b/tests/golden-tests/tests/QuasiQuote.html.ref index d1295f27..a4746d35 100644 --- a/tests/golden-tests/tests/QuasiQuote.html.ref +++ b/tests/golden-tests/tests/QuasiQuote.html.ref @@ -1,4 +1,4 @@ QuasiQuote

       

      QuasiQuote

      Documentation

      \ No newline at end of file +

       

      QuasiQuote

      Documentation

      \ No newline at end of file diff --git a/tests/golden-tests/tests/TH.html.ref b/tests/golden-tests/tests/TH.html.ref index f5e425a8..be34933f 100644 --- a/tests/golden-tests/tests/TH.html.ref +++ b/tests/golden-tests/tests/TH.html.ref @@ -1,4 +1,4 @@ TH

       

      TH

      Documentation

      decl :: Q [Dec]

      \ No newline at end of file +

       

      TH

      Documentation

      decl :: Q [Dec]

      \ No newline at end of file diff --git a/tests/golden-tests/tests/TH2.html.ref b/tests/golden-tests/tests/TH2.html.ref index 4c9e5d04..96d164e4 100644 --- a/tests/golden-tests/tests/TH2.html.ref +++ b/tests/golden-tests/tests/TH2.html.ref @@ -1,4 +1,4 @@ TH2

       

      TH2

      \ No newline at end of file +

       

      TH2

      \ No newline at end of file diff --git a/tests/golden-tests/tests/Test.html.ref b/tests/golden-tests/tests/Test.html.ref index 15380b6c..e4c81c13 100644 --- a/tests/golden-tests/tests/Test.html.ref +++ b/tests/golden-tests/tests/Test.html.ref @@ -15,8 +15,8 @@ window.onload = function () {pageLoad();setSynopsis("mini_Test.html");};

      Description

      This module illustrates & tests most of the features of Haddock. Testing references from the description: T, f, g, visible. -

      Synopsis

      Type declarations -

      Data types +

      Synopsis

      Type declarations +

      Data types

      data T a b

      This comment applies to the following declaration and it continues until the next non-comment line

      Constructors

      A Int (Maybe Float)

      This comment describes the A constructor @@ -39,7 +39,7 @@ window.onload = function () {pageLoad();setSynopsis("mini_Test.html");};

      newtype N6 a b

      Constructors

      N6

      docs on the constructor only

      Fields

      n6 :: a b
       

      newtype N7 a b

      docs on the newtype and the constructor

      Constructors

      N7

      The N7 constructor -

      Fields

      n7 :: a b
       

      Records +

      Fields

      n7 :: a b
       

      Records

      data R

      This is the documentation for the R record, which has four fields, p, q, r, and s.

      Constructors

      C1

      This is the C1 record constructor, with the following fields: @@ -54,14 +54,14 @@ window.onload = function () {pageLoad();setSynopsis("mini_Test.html");};

      s2 :: Int

      The s2 record selector

      s3 :: Int

      The s3 record selector

      test that we can export record selectors on their own: -

      Class declarations +

      Class declarations

      class D a => C a where

      This comment applies to the previous declaration (the C class)

      Methods

      a :: IO a

      this is a description of the a method

      b :: [a]

      this is a description of the b method

      class D a where

      This is a class declaration with no separate docs for the methods

      Methods

      d :: T a b

      e :: (a, a)

      Instances

      class E a

      This is a class declaration with no methods (or no methods exported)

      class F a where

      Methods

      ff :: a

      Test that we can export a class method on its own: -

      Function types +

      Function types

      f :: C a => a -> Int

      In a comment string we can refer to identifiers in scope with single quotes like this: T, and we can refer to modules by using double quotes: Foo. We can add emphasis like this. @@ -79,7 +79,7 @@ using double quotes: Foo. We can add emphasis like this

       this is another block of code
       

      We can also include URLs in documentation: http://www.haskell.org/.

      g :: Int -> IO CInt

      we can export foreign declarations too -

      Auxiliary stuff +

      Auxiliary stuff

      This is some documentation that is attached to a name ($aux1) rather than a source declaration. The documentation may be referred to in the export list using its name. @@ -117,12 +117,12 @@ test2

       a code block using bird-tracks
        each line must begin with > (which isn't significant unless it
        is at the beginning of the line).
      -

      A hidden module -

      hidden :: Int -> Int

      A visible module +

      A hidden module +

      hidden :: Int -> Int

      A visible module

      module Visible

      nested-style doc comments -

      Existential / Universal types +

      Existential / Universal types

      data Ex a

      A data-type using existential/universal types -

      Constructors

      forall b . C b => Ex1 b 
      forall b . Ex2 b 
      forall b . C a => Ex3 b 
      Ex4 (forall a. a -> a) 

      Type signatures with argument docs +

      Constructors

      forall b . C b => Ex1 b 
      forall b . Ex2 b 
      forall b . C a => Ex3 b 
      Ex4 (forall a. a -> a) 

      Type signatures with argument docs

      k

      Arguments

      :: T () ()

      This argument has type T

      -> T2 Int Int

      This argument has type 'T2 Int Int'

      -> (T3 Bool Bool -> T4 Float Float)

      This argument has type T3 Bool Bool -> T4 Float Float @@ -139,10 +139,10 @@ test2

      o

      Arguments

      :: Float

      The input float

      -> IO Float

      The output float

      A foreign import with argument docs -

      A section -

      A subsection +

      A section +

      A subsection

       a literal line
       

      $ a non literal line $

      f' :: Int

      a function with a prime can be referred to as f' but f' doesn't get link'd 'f\'' -

      \ No newline at end of file +

      \ No newline at end of file diff --git a/tests/golden-tests/tests/Ticket112.html.ref b/tests/golden-tests/tests/Ticket112.html.ref index c25d1b4d..e554c794 100644 --- a/tests/golden-tests/tests/Ticket112.html.ref +++ b/tests/golden-tests/tests/Ticket112.html.ref @@ -2,4 +2,4 @@ window.onload = function () {pageLoad();setSynopsis("mini_Ticket112.html");}; //]]>

      Ticket112

      Synopsis

      • f :: a

      Documentation

      f :: a

      ...given a raw Addr# to the string, and the length of the string. -

      \ No newline at end of file +

      \ No newline at end of file diff --git a/tests/golden-tests/tests/Ticket61.html.ref b/tests/golden-tests/tests/Ticket61.html.ref index 08a717af..5abb62a9 100644 --- a/tests/golden-tests/tests/Ticket61.html.ref +++ b/tests/golden-tests/tests/Ticket61.html.ref @@ -2,4 +2,4 @@ window.onload = function () {pageLoad();setSynopsis("mini_Ticket61.html");}; //]]>

      Ticket61

      Documentation

      class C a where

      Methods

      f :: a

      A comment about f -

      \ No newline at end of file +

      \ No newline at end of file diff --git a/tests/golden-tests/tests/Ticket75.html.ref b/tests/golden-tests/tests/Ticket75.html.ref index 473c38a1..0ec179cb 100644 --- a/tests/golden-tests/tests/Ticket75.html.ref +++ b/tests/golden-tests/tests/Ticket75.html.ref @@ -2,4 +2,4 @@ window.onload = function () {pageLoad();setSynopsis("mini_Ticket75.html");}; //]]>

      Ticket75

      Synopsis

      Documentation

      data a :- b

      Constructors

      Q 

      f :: Int

      A reference to :- -

      \ No newline at end of file +

      \ No newline at end of file diff --git a/tests/golden-tests/tests/TypeFamilies.html.ref b/tests/golden-tests/tests/TypeFamilies.html.ref index 7bb68478..ee883c2a 100644 --- a/tests/golden-tests/tests/TypeFamilies.html.ref +++ b/tests/golden-tests/tests/TypeFamilies.html.ref @@ -6,4 +6,4 @@ window.onload = function () {pageLoad();setSynopsis("mini_TypeFamilies.html");};

      Associated Types

      data B a :: * -> *

      An associated type

      Methods

      f :: B a Int

      A method

      Instances

      A Int 

      type family F a

      Doc for family -

      \ No newline at end of file +

      \ No newline at end of file diff --git a/tests/golden-tests/tests/TypeOperators.html.ref b/tests/golden-tests/tests/TypeOperators.html.ref index 15df42df..0e6ec27d 100644 --- a/tests/golden-tests/tests/TypeOperators.html.ref +++ b/tests/golden-tests/tests/TypeOperators.html.ref @@ -2,5 +2,5 @@ window.onload = function () {pageLoad();setSynopsis("mini_TypeOperators.html");}; //]]>

      TypeOperators

      Contents

      Synopsis

      stuff -

      data a :-: b

      data (a :+: b) c

      data Op a b

      newtype O g f a

      Constructors

      O 

      Fields

      unO :: g (f a)
       

      biO :: (g `O` f) a

      newtype Flip (~>) b a

      Constructors

      Flip 

      Fields

      unFlip :: a ~> b
       
      \ No newline at end of file +

      Synopsis

      stuff +

      data a :-: b

      data (a :+: b) c

      data Op a b

      newtype O g f a

      Constructors

      O 

      Fields

      unO :: g (f a)
       

      biO :: (g `O` f) a

      newtype Flip (~>) b a

      Constructors

      Flip 

      Fields

      unFlip :: a ~> b
       
      \ No newline at end of file diff --git a/tests/golden-tests/tests/Visible.html.ref b/tests/golden-tests/tests/Visible.html.ref index 046d4b3f..920338ed 100644 --- a/tests/golden-tests/tests/Visible.html.ref +++ b/tests/golden-tests/tests/Visible.html.ref @@ -1,4 +1,4 @@ Visible

      Visible

      Documentation

      \ No newline at end of file +

      Visible

      Documentation

      \ No newline at end of file -- cgit v1.2.3