Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data Module a = Module {
- moduleName :: String
- moduleSetup :: Maybe a
- moduleContent :: [a]
- moduleConfig :: [Located String]
- data DocTest
- type Interaction = (Expression, ExpectedResult)
- type Expression = String
- type ExpectedResult = [ExpectedLine]
- data ExpectedLine
- data LineChunk
- getDocTests :: [String] -> IO [Module [Located DocTest]]
- parseInteractions :: Located String -> [Located Interaction]
- parseProperties :: Located String -> [Located Expression]
- mkLineChunks :: String -> [LineChunk]
Documentation
Documentation for a module grouped together with the modules name.
Module | |
|
Instances
Functor Module Source # | |
Eq a => Eq (Module a) Source # | |
Show a => Show (Module a) Source # | |
Generic (Module a) Source # | |
NFData a => NFData (Module a) Source # | |
Defined in Test.DocTest.Internal.Extract | |
type Rep (Module a) Source # | |
Defined in Test.DocTest.Internal.Extract type Rep (Module a) = D1 ('MetaData "Module" "Test.DocTest.Internal.Extract" "doctest-parallel-0.2.6-inplace" 'False) (C1 ('MetaCons "Module" 'PrefixI 'True) ((S1 ('MetaSel ('Just "moduleName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: S1 ('MetaSel ('Just "moduleSetup") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe a))) :*: (S1 ('MetaSel ('Just "moduleContent") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [a]) :*: S1 ('MetaSel ('Just "moduleConfig") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Located String])))) |
Instances
type Interaction = (Expression, ExpectedResult) Source #
type Expression = String Source #
type ExpectedResult = [ExpectedLine] Source #
data ExpectedLine Source #
Instances
Eq ExpectedLine Source # | |
Defined in Test.DocTest.Internal.Parse (==) :: ExpectedLine -> ExpectedLine -> Bool # (/=) :: ExpectedLine -> ExpectedLine -> Bool # | |
Show ExpectedLine Source # | |
Defined in Test.DocTest.Internal.Parse showsPrec :: Int -> ExpectedLine -> ShowS # show :: ExpectedLine -> String # showList :: [ExpectedLine] -> ShowS # | |
IsString ExpectedLine Source # | |
Defined in Test.DocTest.Internal.Parse fromString :: String -> ExpectedLine # |
Extract DocTest
s from all given modules and all modules included by the
given modules.
exported for testing
parseInteractions :: Located String -> [Located Interaction] Source #
Extract all interactions from given Haddock comment.
parseProperties :: Located String -> [Located Expression] Source #
Extract all properties from given Haddock comment.
mkLineChunks :: String -> [LineChunk] Source #