diff options
| author | Yuchen Pei <hi@ypei.me> | 2022-08-16 12:24:49 +1000 | 
|---|---|---|
| committer | Yuchen Pei <hi@ypei.me> | 2022-08-16 14:06:43 +1000 | 
| commit | ba880b4c29724768eec5a3c07c79d5525e8b7992 (patch) | |
| tree | 2b99ac288bfffe78c88c97b6984f4cddf71a7421 /org-test | |
| parent | 6b48872222cc21e864e637055d95c71ff911fddf (diff) | |
Adding initial test for the org backend.
Diffstat (limited to 'org-test')
| -rw-r--r-- | org-test/Main.hs | 35 | ||||
| -rw-r--r-- | org-test/ref/main.org | 764 | ||||
| -rw-r--r-- | org-test/run | 6 | ||||
| -rw-r--r-- | org-test/src/Hidden.hs | 7 | ||||
| -rw-r--r-- | org-test/src/Test.hs | 460 | ||||
| -rw-r--r-- | org-test/src/Visible.hs | 4 | 
6 files changed, 1276 insertions, 0 deletions
diff --git a/org-test/Main.hs b/org-test/Main.hs new file mode 100644 index 00000000..01658fd9 --- /dev/null +++ b/org-test/Main.hs @@ -0,0 +1,35 @@ +{-# LANGUAGE CPP #-} + + +import Data.Function +import System.Environment +import System.FilePath + +import Test.Haddock +import Test.Haddock.Utils + + +checkConfig :: CheckConfig String +checkConfig = CheckConfig +    { ccfgRead = Just +    , ccfgClean = const id +    , ccfgDump = id +    , ccfgEqual = (==) +    } + + +dirConfig :: DirConfig +dirConfig = (defaultDirConfig $ takeDirectory __FILE__) +  { dcfgCheckIgnore = checkIgnore +  } + + +main :: IO () +main = do +    cfg <- parseArgs checkConfig dirConfig =<< getArgs +    runAndCheck $ cfg +        { cfgHaddockArgs = cfgHaddockArgs cfg ++ ["--org"] +        } + +checkIgnore :: FilePath -> Bool +checkIgnore file = takeExtension file /= ".org" diff --git a/org-test/ref/main.org b/org-test/ref/main.org new file mode 100644 index 00000000..e4b2b830 --- /dev/null +++ b/org-test/ref/main.org @@ -0,0 +1,764 @@ +*  +  :PROPERTIES: +  :CUSTOM_ID: main +  :Hackage: https://hackage.haskell.org/package/main +  :END: + + + +** Test +   :PROPERTIES: +   :CUSTOM_ID: main.Test +   :Hackage: https://hackage.haskell.org/package/main/docs/Test.html +   :END: + +This module illustrates & tests most of the features of Haddock. Testing references from the description: [[#main.Test.T][T]], [[#main.Test.f][f]], [[#main.Test.g][g]], [[#main.Visible.visible][visible]]. + +*** Type declarations + +**** Data types + +***** data T a b +      :PROPERTIES: +      :CUSTOM_ID: main.Test.T +      :CUSTOM_ID: Test.T +      :END: + +This comment applies to the /following/ declaration and it continues until the next non-comment line + +****** A [[#base.Data.Int.Int][Int]] ([[#base.Data.Maybe.Maybe][Maybe]] [[#base.Prelude.Float][Float]]) +       :PROPERTIES: +       :CUSTOM_ID: main.Test.A:dc +       :CUSTOM_ID: Test.A:dc +       :END: + +This comment describes the [[#main.Test.A:dc][A]] constructor + +****** B ([[#main.Test.T][T]] a b, [[#main.Test.T][T]] [[#base.Data.Int.Int][Int]] [[#base.Prelude.Float][Float]]) +       :PROPERTIES: +       :CUSTOM_ID: main.Test.B:dc +       :CUSTOM_ID: Test.B:dc +       :END: + +This comment describes the [[#main.Test.B:dc][B]] constructor + +***** data T2 a b +      :PROPERTIES: +      :CUSTOM_ID: main.Test.T2 +      :CUSTOM_ID: Test.T2 +      :END: + +An abstract data declaration + +***** data T3 a b +      :PROPERTIES: +      :CUSTOM_ID: main.Test.T3 +      :CUSTOM_ID: Test.T3 +      :END: + +A data declaration with no documentation annotations on the constructors + +****** A1 a +       :PROPERTIES: +       :CUSTOM_ID: main.Test.A1:dc +       :CUSTOM_ID: Test.A1:dc +       :END: + +****** B1 b +       :PROPERTIES: +       :CUSTOM_ID: main.Test.B1:dc +       :CUSTOM_ID: Test.B1:dc +       :END: + +***** data T4 a b +      :PROPERTIES: +      :CUSTOM_ID: main.Test.T4 +      :CUSTOM_ID: Test.T4 +      :END: + +****** A2 a +       :PROPERTIES: +       :CUSTOM_ID: main.Test.A2:dc +       :CUSTOM_ID: Test.A2:dc +       :END: + +****** B2 b +       :PROPERTIES: +       :CUSTOM_ID: main.Test.B2:dc +       :CUSTOM_ID: Test.B2:dc +       :END: + +***** data T5 a b +      :PROPERTIES: +      :CUSTOM_ID: main.Test.T5 +      :CUSTOM_ID: Test.T5 +      :END: + +****** A3 a +       :PROPERTIES: +       :CUSTOM_ID: main.Test.A3:dc +       :CUSTOM_ID: Test.A3:dc +       :END: + +documents [[#main.Test.A3:dc][A3]] + +****** B3 b +       :PROPERTIES: +       :CUSTOM_ID: main.Test.B3:dc +       :CUSTOM_ID: Test.B3:dc +       :END: + +documents [[#main.Test.B3:dc][B3]] + +***** data T6 +      :PROPERTIES: +      :CUSTOM_ID: main.Test.T6 +      :CUSTOM_ID: Test.T6 +      :END: + +Testing alternative comment styles + +****** A4 +       :PROPERTIES: +       :CUSTOM_ID: main.Test.A4:dc +       :CUSTOM_ID: Test.A4:dc +       :END: + +This is the doc for [[#main.Test.A4:dc][A4]] + +****** B4 +       :PROPERTIES: +       :CUSTOM_ID: main.Test.B4:dc +       :CUSTOM_ID: Test.B4:dc +       :END: + +This is the doc for [[#main.Test.B4:dc][B4]] + +****** C4 +       :PROPERTIES: +       :CUSTOM_ID: main.Test.C4:dc +       :CUSTOM_ID: Test.C4:dc +       :END: + +This is the doc for [[#main.Test.C4:dc][C4]] + +***** newtype N1 a +      :PROPERTIES: +      :CUSTOM_ID: main.Test.N1 +      :CUSTOM_ID: Test.N1 +      :END: + +A newtype + +****** N1 a +       :PROPERTIES: +       :CUSTOM_ID: main.Test.N1:dc +       :CUSTOM_ID: Test.N1:dc +       :END: + +***** newtype N2 a b +      :PROPERTIES: +      :CUSTOM_ID: main.Test.N2 +      :CUSTOM_ID: Test.N2 +      :END: + +A newtype with a fieldname + +****** N2 { +       :PROPERTIES: +       :CUSTOM_ID: main.Test.N2:dc +       :CUSTOM_ID: Test.N2:dc +       :END: + +******* n :: a b +        :PROPERTIES: +        :CUSTOM_ID: main.Test.n +        :CUSTOM_ID: Test.n +        :END: + +***** newtype N3 a b +      :PROPERTIES: +      :CUSTOM_ID: main.Test.N3 +      :CUSTOM_ID: Test.N3 +      :END: + +A newtype with a fieldname, documentation on the field + +****** N3 { +       :PROPERTIES: +       :CUSTOM_ID: main.Test.N3:dc +       :CUSTOM_ID: Test.N3:dc +       :END: + +******* n3 :: a b +        :PROPERTIES: +        :CUSTOM_ID: main.Test.n3 +        :CUSTOM_ID: Test.n3 +        :END: + +this is the [[#main.Test.n3][n3]] field + +***** data N4 a b +      :PROPERTIES: +      :CUSTOM_ID: main.Test.N4 +      :CUSTOM_ID: Test.N4 +      :END: + +An abstract newtype - we show this one as data rather than newtype because the difference isn't visible to the programmer for an abstract type. + +***** newtype N5 a b +      :PROPERTIES: +      :CUSTOM_ID: main.Test.N5 +      :CUSTOM_ID: Test.N5 +      :END: + +****** N5 { +       :PROPERTIES: +       :CUSTOM_ID: main.Test.N5:dc +       :CUSTOM_ID: Test.N5:dc +       :END: + +******* n5 :: a b +        :PROPERTIES: +        :CUSTOM_ID: main.Test.n5 +        :CUSTOM_ID: Test.n5 +        :END: + +no docs on the datatype or the constructor + +***** newtype N6 a b +      :PROPERTIES: +      :CUSTOM_ID: main.Test.N6 +      :CUSTOM_ID: Test.N6 +      :END: + +****** N6 { +       :PROPERTIES: +       :CUSTOM_ID: main.Test.N6:dc +       :CUSTOM_ID: Test.N6:dc +       :END: + +docs on the constructor only + +******* n6 :: a b +        :PROPERTIES: +        :CUSTOM_ID: main.Test.n6 +        :CUSTOM_ID: Test.n6 +        :END: + +***** newtype N7 a b +      :PROPERTIES: +      :CUSTOM_ID: main.Test.N7 +      :CUSTOM_ID: Test.N7 +      :END: + +docs on the newtype and the constructor + +****** N7 { +       :PROPERTIES: +       :CUSTOM_ID: main.Test.N7:dc +       :CUSTOM_ID: Test.N7:dc +       :END: + +The [[#main.Test.N7][N7]] constructor + +******* n7 :: a b +        :PROPERTIES: +        :CUSTOM_ID: main.Test.n7 +        :CUSTOM_ID: Test.n7 +        :END: + +**** Records + +***** data R +      :PROPERTIES: +      :CUSTOM_ID: main.Test.R +      :CUSTOM_ID: Test.R +      :END: + +This is the documentation for the [[#main.Test.R][R]] record, which has four fields, [[#main.Test.p][p]], [[#main.Test.q][q]], [[#main.Test.r][r]], and [[#main.Test.s][s]]. + +****** C1 { +       :PROPERTIES: +       :CUSTOM_ID: main.Test.C1:dc +       :CUSTOM_ID: Test.C1:dc +       :END: + +This is the [[#main.Test.C1:dc][C1]] record constructor, with the following fields: + +******* p :: [[#base.Data.Int.Int][Int]] +        :PROPERTIES: +        :CUSTOM_ID: main.Test.p +        :CUSTOM_ID: Test.p +        :END: + +This comment applies to the [[#main.Test.p][p]] field + +******* q :: forall a. a -> a +        :PROPERTIES: +        :CUSTOM_ID: main.Test.q +        :CUSTOM_ID: Test.q +        :END: + +This comment applies to the [[#main.Test.q][q]] field + +******* r, s :: [[#base.Data.Int.Int][Int]] +        :PROPERTIES: +        :CUSTOM_ID: main.Test.r +        :CUSTOM_ID: Test.r +        :CUSTOM_ID: main.Test.s +        :CUSTOM_ID: Test.s +        :END: + +This comment applies to both [[#main.Test.r][r]] and [[#main.Test.s][s]] + +****** C2 { +       :PROPERTIES: +       :CUSTOM_ID: main.Test.C2:dc +       :CUSTOM_ID: Test.C2:dc +       :END: + +This is the [[#main.Test.C2:dc][C2]] record constructor, also with some fields: + +******* t :: [[#main.Test.T1][T1]] -> ([[#main.Test.T2][T2]] [[#base.Data.Int.Int][Int]] [[#base.Data.Int.Int][Int]]) -> ([[#main.Test.T3][T3]] [[#base.Data.Bool.Bool][Bool]] [[#base.Data.Bool.Bool][Bool]]) -> ([[#main.Test.T4][T4]] [[#base.Prelude.Float][Float]] [[#base.Prelude.Float][Float]]) -> [[#main.Test.T5][T5]] () () +        :PROPERTIES: +        :CUSTOM_ID: main.Test.t +        :CUSTOM_ID: Test.t +        :END: + +******* u, v :: [[#base.Data.Int.Int][Int]] +        :PROPERTIES: +        :CUSTOM_ID: main.Test.u +        :CUSTOM_ID: Test.u +        :CUSTOM_ID: main.Test.v +        :CUSTOM_ID: Test.v +        :END: + +***** data R1 +      :PROPERTIES: +      :CUSTOM_ID: main.Test.R1 +      :CUSTOM_ID: Test.R1 +      :END: + +Testing different record commenting styles + +****** C3 { +       :PROPERTIES: +       :CUSTOM_ID: main.Test.C3:dc +       :CUSTOM_ID: Test.C3:dc +       :END: + +This is the [[#main.Test.C3:dc][C3]] record constructor + +******* s1 :: [[#base.Data.Int.Int][Int]] +        :PROPERTIES: +        :CUSTOM_ID: main.Test.s1 +        :CUSTOM_ID: Test.s1 +        :END: + +The [[#main.Test.s1][s1]] record selector + +******* s2 :: [[#base.Data.Int.Int][Int]] +        :PROPERTIES: +        :CUSTOM_ID: main.Test.s2 +        :CUSTOM_ID: Test.s2 +        :END: + +The [[#main.Test.s2][s2]] record selector + +******* s3 :: [[#base.Data.Int.Int][Int]] +        :PROPERTIES: +        :CUSTOM_ID: main.Test.s3 +        :CUSTOM_ID: Test.s3 +        :END: + +The [[#main.Test.s3][s3]] record selector + +test that we can export record selectors on their own: + +***** p :: [[#main.Test.R][R]] -> [[#base.Data.Int.Int][Int]] +      :PROPERTIES: +      :CUSTOM_ID: main.Test.p +      :CUSTOM_ID: Test.p +      :END: + +This comment applies to the [[#main.Test.p][p]] field + +***** q :: [[#main.Test.R][R]] -> forall a. a -> a +      :PROPERTIES: +      :CUSTOM_ID: main.Test.q +      :CUSTOM_ID: Test.q +      :END: + +This comment applies to the [[#main.Test.q][q]] field + +***** u :: [[#main.Test.R][R]] -> [[#base.Data.Int.Int][Int]] +      :PROPERTIES: +      :CUSTOM_ID: main.Test.u +      :CUSTOM_ID: Test.u +      :END: + +*** Class declarations + +**** class ([[#main.Test.D][D]] a) => C a +     :PROPERTIES: +     :CUSTOM_ID: main.Test.C +     :CUSTOM_ID: Test.C +     :END: + +This comment applies to the /previous/ declaration (the [[#main.Test.C][C]] class) + +***** a :: [[#base.System.IO.IO][IO]] a +      :PROPERTIES: +      :CUSTOM_ID: main.Test.a +      :CUSTOM_ID: Test.a +      :END: + +this is a description of the [[#main.Test.a][a]] method + +***** b :: [a] +      :PROPERTIES: +      :CUSTOM_ID: main.Test.b +      :CUSTOM_ID: Test.b +      :END: + +this is a description of the [[#main.Test.b][b]] method + +**** class D a +     :PROPERTIES: +     :CUSTOM_ID: main.Test.D +     :CUSTOM_ID: Test.D +     :END: + +This is a class declaration with no separate docs for the methods + +***** d :: [[#main.Test.T][T]] a b +      :PROPERTIES: +      :CUSTOM_ID: main.Test.d +      :CUSTOM_ID: Test.d +      :END: + +***** e :: (a, a) +      :PROPERTIES: +      :CUSTOM_ID: main.Test.e +      :CUSTOM_ID: Test.e +      :END: + +***** Instances: + +- [[#main.Test.D][D]] [[#base.Prelude.Float][Float]] +- [[#main.Test.D][D]] [[#base.Data.Int.Int][Int]] + +**** class E a +     :PROPERTIES: +     :CUSTOM_ID: main.Test.E +     :CUSTOM_ID: Test.E +     :END: + +This is a class declaration with no methods (or no methods exported) + +**** class F a +     :PROPERTIES: +     :CUSTOM_ID: main.Test.F +     :CUSTOM_ID: Test.F +     :END: + +***** ff :: a +      :PROPERTIES: +      :CUSTOM_ID: main.Test.ff +      :CUSTOM_ID: Test.ff +      :END: + +Test that we can export a class method on its own: + +**** a :: [[#main.Test.C][C]] a => [[#base.System.IO.IO][IO]] a +     :PROPERTIES: +     :CUSTOM_ID: main.Test.a +     :CUSTOM_ID: Test.a +     :END: + +this is a description of the [[#main.Test.a][a]] method + +*** Function types + +**** f :: [[#main.Test.C][C]] a => a -> [[#base.Data.Int.Int][Int]] +     :PROPERTIES: +     :CUSTOM_ID: main.Test.f +     :CUSTOM_ID: Test.f +     :END: + +In a comment string we can refer to identifiers in scope with single quotes like this: [[#main.Test.T][T]], and we can refer to modules by using double quotes: [[Foo]].  We can add emphasis /like this/. + +- This is a bulleted list +- This is the next item (different kind of bullet) + +1. This is an ordered list +2. This is the next item (different kind of bullet) + +- cat :: a small, furry, domesticated mammal +- pineapple :: a fruit grown in the tropics + +#+begin_src haskell +     This is a block of code, which can include other markup: R +     formatting +               is +                 significant +#+end_src + +#+begin_src haskell +this is another block of code +#+end_src + +We can also include URLs in documentation: [[http://www.haskell.org/]]. + +**** g :: [[#base.Data.Int.Int][Int]] -> [[#base.System.IO.IO][IO]] [[#main.Test.CInt][CInt]] +     :PROPERTIES: +     :CUSTOM_ID: main.Test.g +     :CUSTOM_ID: Test.g +     :END: + +we can export foreign declarations too + +*** 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. + +#+begin_src haskell + code block in named doc +#+end_src + +This is some documentation that is attached to a name ($aux2) + +#+begin_src haskell + code block on its own in named doc +#+end_src + +#+begin_src haskell + code block on its own in named doc (after newline) +#+end_src + +a nested, named doc comment + +with a paragraph, + +#+begin_src haskell + and a code block +#+end_src + +#+begin_src haskell +test +test1 +#+end_src + +#+begin_src haskell + test2 +  test3 +#+end_src + +#+begin_src haskell +test1 +test2 +#+end_src + +#+begin_src haskell +test3 +test4 +#+end_src + +#+begin_src haskell +test1 +test2 +#+end_src + +#+begin_src haskell +test3 +test4 +#+end_src + +#+begin_src haskell +test3 +test4 +#+end_src + +#+begin_src haskell +test1 +test2 +#+end_src + +aux11: + +#+begin_src haskell +test3 +test4 +#+end_src + +#+begin_src haskell +test1 +test2 +#+end_src + +#+begin_src haskell +foo +#+end_src + +#+begin_src haskell +bar +#+end_src + +This is some inline documentation in the export list + +#+begin_src haskell +a code block using bird-tracks +each line must begin with > (which isn't significant unless it +is at the beginning of the line). +#+end_src + +*** A hidden module + +**** hidden :: [[#base.Data.Int.Int][Int]] -> [[#base.Data.Int.Int][Int]] +     :PROPERTIES: +     :CUSTOM_ID: main.Test.hidden +     :CUSTOM_ID: Test.hidden +     :END: + +*** A visible module + +**** module [[Visible]] + +nested-style doc comments  + +*** Existential / Universal types + +**** data Ex a +     :PROPERTIES: +     :CUSTOM_ID: main.Test.Ex +     :CUSTOM_ID: Test.Ex +     :END: + +A data-type using existential/universal types + +***** forall b. [[#main.Test.C][C]] b => Ex1 b +      :PROPERTIES: +      :CUSTOM_ID: main.Test.Ex1:dc +      :CUSTOM_ID: Test.Ex1:dc +      :END: + +***** forall b. Ex2 b +      :PROPERTIES: +      :CUSTOM_ID: main.Test.Ex2:dc +      :CUSTOM_ID: Test.Ex2:dc +      :END: + +***** forall b. [[#main.Test.C][C]] a => Ex3 b +      :PROPERTIES: +      :CUSTOM_ID: main.Test.Ex3:dc +      :CUSTOM_ID: Test.Ex3:dc +      :END: + +***** Ex4 (forall a. a -> a) +      :PROPERTIES: +      :CUSTOM_ID: main.Test.Ex4:dc +      :CUSTOM_ID: Test.Ex4:dc +      :END: + +*** Type signatures with argument docs + +**** k :: [[#main.Test.T][T]] () () -> [[#main.Test.T2][T2]] [[#base.Data.Int.Int][Int]] [[#base.Data.Int.Int][Int]] -> ([[#main.Test.T3][T3]] [[#base.Data.Bool.Bool][Bool]] [[#base.Data.Bool.Bool][Bool]] -> [[#main.Test.T4][T4]] [[#base.Prelude.Float][Float]] [[#base.Prelude.Float][Float]]) -> [[#main.Test.T5][T5]] () () -> [[#base.System.IO.IO][IO]] () +     :PROPERTIES: +     :CUSTOM_ID: main.Test.k +     :CUSTOM_ID: Test.k +     :END: + +Arguments: + +- [[#main.Test.T][T]] () () :: This argument has type [[#main.Test.T][T]] +- ([[#main.Test.T2][T2]] [[#base.Data.Int.Int][Int]] [[#base.Data.Int.Int][Int]]) :: This argument has type 'T2 Int Int' +- ([[#main.Test.T3][T3]] [[#base.Data.Bool.Bool][Bool]] [[#base.Data.Bool.Bool][Bool]] -> [[#main.Test.T4][T4]] [[#base.Prelude.Float][Float]] [[#base.Prelude.Float][Float]]) :: This argument has type ~T3 Bool Bool -> T4 Float Float~ +- [[#main.Test.T5][T5]] () () :: This argument has a very long description that should hopefully cause some wrapping to happen when it is finally rendered by Haddock in the generated HTML page. +- [[#base.System.IO.IO][IO]] () :: This is the result type + +This is a function with documentation for each argument + +**** l :: ([[#base.Data.Int.Int][Int]], [[#base.Data.Int.Int][Int]], [[#base.Prelude.Float][Float]]) -> [[#base.Data.Int.Int][Int]] +     :PROPERTIES: +     :CUSTOM_ID: main.Test.l +     :CUSTOM_ID: Test.l +     :END: + +Arguments: + +- ([[#base.Data.Int.Int][Int]], [[#base.Data.Int.Int][Int]], [[#base.Prelude.Float][Float]]) :: takes a triple +- [[#base.Data.Int.Int][Int]] :: returns an [[#base.Data.Int.Int][Int]] + +**** m :: [[#main.Test.R][R]] -> [[#main.Test.N1][N1]] () -> [[#base.System.IO.IO][IO]] [[#base.Data.Int.Int][Int]] +     :PROPERTIES: +     :CUSTOM_ID: main.Test.m +     :CUSTOM_ID: Test.m +     :END: + +Arguments: + +- [[#main.Test.R][R]] ::  +- [[#main.Test.N1][N1]] () :: one of the arguments +- [[#base.System.IO.IO][IO]] [[#base.Data.Int.Int][Int]] :: and the return value + +This function has some arg docs + +**** o :: [[#base.Prelude.Float][Float]] -> [[#base.System.IO.IO][IO]] [[#base.Prelude.Float][Float]] +     :PROPERTIES: +     :CUSTOM_ID: main.Test.o +     :CUSTOM_ID: Test.o +     :END: + +Arguments (in order): + +1. The input float +2. The output float + +A foreign import with argument docs + +*** A section + +**** A subsection + +#+begin_src haskell +a literal line +#+end_src + +$ a non /literal/ line $ + +***** f' :: [[#base.Data.Int.Int][Int]] +      :PROPERTIES: +      :CUSTOM_ID: main.Test.f' +      :CUSTOM_ID: Test.f' +      :END: + +a function with a prime can be referred to as [[#main.Test.f'][f']] but f' doesn't get link'd 'f'' + +***** withType :: [[#base.Data.Int.Int][Int]] +      :PROPERTIES: +      :CUSTOM_ID: main.Test.withType +      :CUSTOM_ID: Test.withType +      :END: + +Comment on a definition with type signature + +***** withoutType :: a +      :PROPERTIES: +      :CUSTOM_ID: main.Test.withoutType +      :CUSTOM_ID: Test.withoutType +      :END: + +Comment on a definition without type signature + +** Visible +   :PROPERTIES: +   :CUSTOM_ID: main.Visible +   :Hackage: https://hackage.haskell.org/package/main/docs/Visible.html +   :END: + +*** visible :: [[#base.Data.Int.Int][Int]] -> [[#base.Data.Int.Int][Int]] +    :PROPERTIES: +    :CUSTOM_ID: main.Visible.visible +    :CUSTOM_ID: Visible.visible +    :END: diff --git a/org-test/run b/org-test/run new file mode 100644 index 00000000..3e72be80 --- /dev/null +++ b/org-test/run @@ -0,0 +1,6 @@ +#!/usr/bin/env bash + +export HADDOCK_PATH=$(which haddock) +LIB_PATH="$(dirname "$BASH_SOURCE")/../haddock-test/src/" +MAIN_PATH="$(dirname "$BASH_SOURCE")/Main.hs" +runhaskell -i:"$LIB_PATH" $MAIN_PATH $@ diff --git a/org-test/src/Hidden.hs b/org-test/src/Hidden.hs new file mode 100644 index 00000000..2b694e86 --- /dev/null +++ b/org-test/src/Hidden.hs @@ -0,0 +1,7 @@ +{-# LANGUAGE Haskell2010 #-} +{-# OPTIONS_HADDOCK hide #-} + +module Hidden where + +hidden :: Int -> Int +hidden a = a diff --git a/org-test/src/Test.hs b/org-test/src/Test.hs new file mode 100644 index 00000000..d5632bfa --- /dev/null +++ b/org-test/src/Test.hs @@ -0,0 +1,460 @@ +{-# LANGUAGE Haskell2010 #-} +----------------------------------------------------------------------------- +-- | +-- Module      :  Test +-- Copyright   :  (c) Simon Marlow 2002 +-- License     :  BSD-style +-- +-- Maintainer  :  libraries@haskell.org +-- Stability   :  provisional +-- Portability :  portable +-- +-- This module illustrates & tests most of the features of Haddock. +-- Testing references from the description: 'T', 'f', 'g', 'Visible.visible'. +-- +----------------------------------------------------------------------------- + +-- This is plain comment, ignored by Haddock. +{-# LANGUAGE Rank2Types, GADTs #-} +module Test +  ( + +        -- Section headings are introduced with '-- *': +        -- * Type declarations + +        -- Subsection headings are introduced with '-- **' and so on. +        -- ** Data types +    T(..) +  , T2 +  , T3(..) +  , T4(..) +  , T5(..) +  , T6(..) +  , N1(..) +  , N2(..) +  , N3(..) +  , N4 +  , N5(..) +  , N6(..) +  , N7(..) +  , + +        -- ** Records +    R(..) +  , R1(..) +  , + +        -- | test that we can export record selectors on their own: +    p +  , q +  , u +  , + +        -- * Class declarations +    C(a, b) +  , D(..) +  , E +  , F(..) +  , + +        -- | Test that we can export a class method on its own: +    a +  , + +        -- * Function types +    f +  , g +  , + +        -- * Auxiliary stuff + +        -- $aux1 + +        -- $aux2 + +        -- $aux3 + +        -- $aux4 + +        -- $aux5 + +        -- $aux6 + +        -- $aux7 + +        -- $aux8 + +        -- $aux9 + +        -- $aux10 + +        -- $aux11 + +        -- $aux12 + +        -- | This is some inline documentation in the export list +        -- +        -- > 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 +    module Hidden +  , + +        -- * A visible module +    module Visible +  , + +        {-| nested-style doc comments -} + +        -- * Existential \/ Universal types +    Ex(..) +  , + +        -- * Type signatures with argument docs +    k +  , l +  , m +  , o +  , + +        -- * A section +        -- and without an intervening comma: +        -- ** A subsection + +{-| + > a literal line + + $ a non /literal/ line $ +-} +    f' +  , withType +  , withoutType +  ) where + +import           Data.Maybe +import           Hidden +import           Visible + +bla = Nothing + +-- | This comment applies to the /following/ declaration +-- and it continues until the next non-comment line +data T a b + = A Int (Maybe Float) -- ^ This comment describes the 'A' constructor + | -- | This comment describes the 'B' constructor +   B (T a b, T Int Float) -- ^ + +-- | An abstract data declaration +data T2 a b = T2 a b + +-- | A data declaration with no documentation annotations on the constructors +data T3 a b = A1 a | B1 b + +-- A data declaration with no documentation annotations at all +data T4 a b = A2 a | B2 b + +-- A data declaration documentation on the constructors only +data T5 a b +  = A3 a -- ^ documents 'A3' +  | B3 b -- ^ documents 'B3' + +-- | Testing alternative comment styles +data T6 +  -- | This is the doc for 'A4' +  = A4 +  | B4 +  | -- ^ This is the doc for 'B4' + +    -- | This is the doc for 'C4' +    C4 + +-- | A newtype +newtype N1 a = N1 a + +-- | A newtype with a fieldname +newtype N2 a b = N2 {n :: a b} + +-- | A newtype with a fieldname, documentation on the field +newtype N3 a b = N3 {n3 :: a b -- ^ this is the 'n3' field +                    } + +-- | An abstract newtype - we show this one as data rather than newtype because +-- the difference isn\'t visible to the programmer for an abstract type. +newtype N4 a b = N4 a + +newtype N5 a b = N5 {n5 :: a b -- ^ no docs on the datatype or the constructor +                    } + +newtype N6 a b = N6 {n6 :: a b +                    } +                 -- ^ docs on the constructor only + +-- | docs on the newtype and the constructor +newtype N7 a b = N7 {n7 :: a b +                    } +                -- ^ The 'N7' constructor + + +class (D a) => C a  where +   -- |this is a description of the 'a' method +   a :: IO a +   b :: [a] +   -- ^ this is a description of the 'b' method +   c :: a -- c is hidden in the export list +   c = undefined + +-- ^ This comment applies to the /previous/ declaration (the 'C' class) + +class D a where +   d :: T a b +   e :: (a,a) +-- ^ This is a class declaration with no separate docs for the methods + +instance D Int where +  d = undefined +  e = undefined + +-- instance with a qualified class name +instance Test.D Float where +  d = undefined +  e = undefined + +class E a where +  ee :: a +-- ^ This is a class declaration with no methods (or no methods exported) + +-- This is a class declaration with no documentation at all +class F a where +  ff :: a + +-- | This is the documentation for the 'R' record, which has four fields, +-- 'p', 'q', 'r', and 's'. +data R = +  -- | This is the 'C1' record constructor, with the following fields: +  C1 { p :: Int -- ^ This comment applies to the 'p' field +     , q :: forall a . a->a  -- ^ This comment applies to the 'q' field +     , -- | This comment applies to both 'r' and 's' +       r,s :: Int +     } +  | C2 { t :: T1 -> (T2 Int Int)-> (T3 Bool Bool) -> (T4 Float Float) -> T5 () (), +       u,v :: Int +     } +  -- ^ This is the 'C2' record constructor, also with some fields: + +-- | Testing different record commenting styles +data R1 +  -- | This is the 'C3' record constructor +        = C3 +  { +              -- | The 's1' record selector +    s1 :: Int +              -- | The 's2' record selector +  , s2 :: Int +  , s3 :: Int  -- NOTE: In the original examples/Test.hs in Haddock, there is an extra "," here. +                           -- Since GHC doesn't allow that, I have removed it in this file. +              -- ^ The 's3' record selector +  } + +-- These section headers are only used when there is no export list to +-- give the structure of the documentation: + +-- * This is a section header (level 1) +-- ** This is a section header (level 2) +-- *** This is a section header (level 3) + +{-| +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/. + +   * This is a bulleted list + +   - This is the next item (different kind of bullet) + +   (1) This is an ordered list + +   2. This is the next item (different kind of bullet) + +   [cat] a small, furry, domesticated mammal + +   [pineapple] a fruit grown in the tropics + +@ +     This is a block of code, which can include other markup: 'R' +     formatting +               is +                 significant +@ + +> this is another block of code + +We can also include URLs in documentation: <http://www.haskell.org/>. +-} + +f :: C a => a -> Int + +-- | we can export foreign declarations too +foreign import ccall g :: Int -> IO CInt + +-- | this doc string has a parse error in it: \' +h :: Int +h = 42 + + +-- $aux1 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. +-- +-- @ code block in named doc @ + +-- $aux2 This is some documentation that is attached to a name ($aux2) + +-- $aux3 +-- @ code block on its own in named doc @ + +-- $aux4 +-- +-- @ code block on its own in named doc (after newline) @ + +{- $aux5 a nested, named doc comment + +   with a paragraph, + +   @ and a code block @ +-} + +-- some tests for various arrangements of code blocks: + +{- $aux6 +>test +>test1 + +@ test2 +  test3 +@ +-} + +{- $aux7 +@ +test1 +test2 +@ +-} + +{- $aux8 +>test3 +>test4 +-} + +{- $aux9 +@ +test1 +test2 +@ + +>test3 +>test4 +-} + +{- $aux10 +>test3 +>test4 + +@ +test1 +test2 +@ +-} + +-- This one is currently wrong (Haddock 0.4).  The @...@ part is +-- interpreted as part of the bird-tracked code block. +{- $aux11 +aux11: + +>test3 +>test4 + +@ +test1 +test2 +@ +-} + +-- $aux12 +-- > foo +-- +-- > bar +-- + +-- | A data-type using existential\/universal types +data Ex a +  = forall b . C b => Ex1 b +  | forall b . Ex2 b +  | forall b . C a => Ex3 b -- NOTE: I have added "forall b" here make GHC accept this file +  | Ex4 (forall a . a -> a) + +-- | This is a function with documentation for each argument +k +  :: 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@ +  -> T5 () ()     -- ^ This argument has a very long description that should +                  -- hopefully cause some wrapping to happen when it is finally +                  -- rendered by Haddock in the generated HTML page. +  -> IO ()        -- ^ This is the result type + +-- This function has arg docs but no docs for the function itself +l +  :: (Int, Int, Float) -- ^ takes a triple +  -> Int -- ^ returns an 'Int' + +-- | This function has some arg docs +m +  :: R +  -> N1 ()      -- ^ one of the arguments +  -> IO Int     -- ^ and the return value + +-- | This function has some arg docs but not a return value doc + +-- can't use the original name ('n') with GHC +newn +  :: R               -- ^ one of the arguments, an 'R' +  -> N1 ()           -- ^ one of the arguments +  -> IO Int +newn = undefined + + +-- | A foreign import with argument docs +foreign import ccall unsafe + o :: Float  -- ^ The input float +   -> IO Float  -- ^ The output float + +-- | We should be able to escape this: \#\#\# + +-- p :: Int +-- can't use the above original definition with GHC +newp :: Int +newp = undefined + +-- | a function with a prime can be referred to as 'f'' +-- but f' doesn't get link'd 'f\'' +f' :: Int + +-- | Comment on a definition without type signature +withoutType = undefined + +-- | Comment on a definition with type signature +withType :: Int +withType = 1 + +-- Add some definitions here so that this file can be compiled with GHC + +data T1 +f = undefined +f' = undefined +type CInt = Int +k = undefined +l = undefined +m = undefined diff --git a/org-test/src/Visible.hs b/org-test/src/Visible.hs new file mode 100644 index 00000000..9440aeef --- /dev/null +++ b/org-test/src/Visible.hs @@ -0,0 +1,4 @@ +{-# LANGUAGE Haskell2010 #-} +module Visible where +visible :: Int -> Int +visible a = a  | 
