pandoc/test/Tests/Readers/Org.hs
Albert Krewinkel 37a82b0b11 Add missing copyright notices and remove license boilerplate (#5112)
Quite a few modules were missing copyright notices.

This commit adds copyright notices everywhere via haddock module
headers.  The old license boilerplate comment is redundant with this and has
been removed.

Update copyright years to 2019.

Closes #4592.
2019-02-04 13:52:31 -08:00

27 lines
783 B
Haskell

{-# LANGUAGE OverloadedStrings #-}
{- |
Module : Tests.Shared
Copyright : © 2014-2019 Albert Krewinkel
License : GNU GPL, version 2 or above
Maintainer : Albert Krewinkel <albert@zeitkraut.de>
Stability : alpha
Portability : portable
Tests of the org reader.
-}
module Tests.Readers.Org (tests) where
import Test.Tasty (TestTree, testGroup)
import qualified Tests.Readers.Org.Block as Block
import qualified Tests.Readers.Org.Directive as Directive
import qualified Tests.Readers.Org.Inline as Inline
import qualified Tests.Readers.Org.Meta as Meta
tests :: [TestTree]
tests =
[ testGroup "Inlines" Inline.tests
, testGroup "Basic Blocks" Block.tests
, testGroup "Meta Information" Meta.tests
, testGroup "Directives" Directive.tests
]