output-blocks-0.5.0.1
Safe HaskellNone
LanguageHaskell2010

Control.OutputCapable.Blocks

Description

This module provides common skeletons for printing tasks

Synopsis

Documentation

class (forall (g :: Type -> Type). Functor g => Functor (t g)) => FunctorTrans (t :: (Type -> Type) -> Type -> Type) where Source #

The class of functor transformers.

Lifting a functor to the stacked functor.

Methods

lift :: Functor f => f a -> t f a Source #

Lift a computation from the argument functor to the constructed functor.

Instances

Instances details
FunctorTrans (GenericLangM l) Source # 
Instance details

Defined in Control.OutputCapable.Blocks.Generic

Methods

lift :: Functor f => f a -> GenericLangM l f a Source #

Report monad

data GenericOut l o Source #

Constructors

Format o 
Localised (l -> o) 

Instances

Instances details
Functor (GenericOut l) Source # 
Instance details

Defined in Control.OutputCapable.Blocks.Report.Generic

Methods

fmap :: (a -> b) -> GenericOut l a -> GenericOut l b #

(<$) :: a -> GenericOut l b -> GenericOut l a #

newtype GenericReportT l o (m :: Type -> Type) r Source #

Constructors

Report 

Fields

Instances

Instances details
l ~ Language => GenericOutputCapable l (GenericReportT l (IO ()) IO) Source # 
Instance details

Defined in Control.OutputCapable.Blocks

Methods

assertion :: Bool -> GenericLangM l (GenericReportT l (IO ()) IO) () -> GenericLangM l (GenericReportT l (IO ()) IO) () Source #

image :: FilePath -> GenericLangM l (GenericReportT l (IO ()) IO) () Source #

images :: (k -> String) -> (a -> FilePath) -> Map k a -> GenericLangM l (GenericReportT l (IO ()) IO) () Source #

paragraph :: GenericLangM l (GenericReportT l (IO ()) IO) () -> GenericLangM l (GenericReportT l (IO ()) IO) () Source #

refuse :: GenericLangM l (GenericReportT l (IO ()) IO) () -> GenericLangM l (GenericReportT l (IO ()) IO) () Source #

text :: String -> GenericLangM l (GenericReportT l (IO ()) IO) () Source #

enumerateM :: (a -> GenericLangM l (GenericReportT l (IO ()) IO) ()) -> [(a, GenericLangM l (GenericReportT l (IO ()) IO) ())] -> GenericLangM l (GenericReportT l (IO ()) IO) () Source #

itemizeM :: [GenericLangM l (GenericReportT l (IO ()) IO) ()] -> GenericLangM l (GenericReportT l (IO ()) IO) () Source #

indent :: GenericLangM l (GenericReportT l (IO ()) IO) () -> GenericLangM l (GenericReportT l (IO ()) IO) () Source #

latex :: String -> GenericLangM l (GenericReportT l (IO ()) IO) () Source #

folded :: Bool -> (l -> String) -> GenericLangM l (GenericReportT l (IO ()) IO) () -> GenericLangM l (GenericReportT l (IO ()) IO) () Source #

code :: String -> GenericLangM l (GenericReportT l (IO ()) IO) () Source #

translatedCode :: (l -> String) -> GenericLangM l (GenericReportT l (IO ()) IO) () Source #

translated :: (l -> String) -> GenericLangM l (GenericReportT l (IO ()) IO) () Source #

(Bounded language, Enum language, Monad m, Ord language) => GenericOutputCapable language (GenericReportT language (GenericOutput language element) m) Source #

OutputCapable instances for GenericOutput, allowing for free conversion between ADT and interface.

Instance details

Defined in Control.OutputCapable.Blocks.Generic.Type

Methods

assertion :: Bool -> GenericLangM language (GenericReportT language (GenericOutput language element) m) () -> GenericLangM language (GenericReportT language (GenericOutput language element) m) () Source #

image :: FilePath -> GenericLangM language (GenericReportT language (GenericOutput language element) m) () Source #

images :: (k -> String) -> (a -> FilePath) -> Map k a -> GenericLangM language (GenericReportT language (GenericOutput language element) m) () Source #

paragraph :: GenericLangM language (GenericReportT language (GenericOutput language element) m) () -> GenericLangM language (GenericReportT language (GenericOutput language element) m) () Source #

refuse :: GenericLangM language (GenericReportT language (GenericOutput language element) m) () -> GenericLangM language (GenericReportT language (GenericOutput language element) m) () Source #

text :: String -> GenericLangM language (GenericReportT language (GenericOutput language element) m) () Source #

enumerateM :: (a -> GenericLangM language (GenericReportT language (GenericOutput language element) m) ()) -> [(a, GenericLangM language (GenericReportT language (GenericOutput language element) m) ())] -> GenericLangM language (GenericReportT language (GenericOutput language element) m) () Source #

itemizeM :: [GenericLangM language (GenericReportT language (GenericOutput language element) m) ()] -> GenericLangM language (GenericReportT language (GenericOutput language element) m) () Source #

indent :: GenericLangM language (GenericReportT language (GenericOutput language element) m) () -> GenericLangM language (GenericReportT language (GenericOutput language element) m) () Source #

latex :: String -> GenericLangM language (GenericReportT language (GenericOutput language element) m) () Source #

folded :: Bool -> (language -> String) -> GenericLangM language (GenericReportT language (GenericOutput language element) m) () -> GenericLangM language (GenericReportT language (GenericOutput language element) m) () Source #

code :: String -> GenericLangM language (GenericReportT language (GenericOutput language element) m) () Source #

translatedCode :: (language -> String) -> GenericLangM language (GenericReportT language (GenericOutput language element) m) () Source #

translated :: (language -> String) -> GenericLangM language (GenericReportT language (GenericOutput language element) m) () Source #

l ~ Language => RunnableOutputCapable l (GenericReportT l (IO ()) IO) Source # 
Instance details

Defined in Control.OutputCapable.Blocks

Associated Types

type RunMonad l (GenericReportT l (IO ()) IO) 
Instance details

Defined in Control.OutputCapable.Blocks

type RunMonad l (GenericReportT l (IO ()) IO) = IO
type Output l (GenericReportT l (IO ()) IO) 
Instance details

Defined in Control.OutputCapable.Blocks

type Output l (GenericReportT l (IO ()) IO) = IO ()

Methods

runLangM :: GenericLangM l (GenericReportT l (IO ()) IO) a -> RunMonad l (GenericReportT l (IO ()) IO) (Maybe a, l -> Output l (GenericReportT l (IO ()) IO)) Source #

MonadTrans (GenericReportT l o) Source # 
Instance details

Defined in Control.OutputCapable.Blocks.Report.Generic

Methods

lift :: Monad m => m a -> GenericReportT l o m a #

MonadIO m => MonadIO (GenericReportT l o m) Source # 
Instance details

Defined in Control.OutputCapable.Blocks.Report.Generic

Methods

liftIO :: IO a -> GenericReportT l o m a #

Monad m => Alternative (GenericReportT l o m) Source # 
Instance details

Defined in Control.OutputCapable.Blocks.Report.Generic

Methods

empty :: GenericReportT l o m a #

(<|>) :: GenericReportT l o m a -> GenericReportT l o m a -> GenericReportT l o m a #

some :: GenericReportT l o m a -> GenericReportT l o m [a] #

many :: GenericReportT l o m a -> GenericReportT l o m [a] #

Monad m => Applicative (GenericReportT l o m) Source # 
Instance details

Defined in Control.OutputCapable.Blocks.Report.Generic

Methods

pure :: a -> GenericReportT l o m a #

(<*>) :: GenericReportT l o m (a -> b) -> GenericReportT l o m a -> GenericReportT l o m b #

liftA2 :: (a -> b -> c) -> GenericReportT l o m a -> GenericReportT l o m b -> GenericReportT l o m c #

(*>) :: GenericReportT l o m a -> GenericReportT l o m b -> GenericReportT l o m b #

(<*) :: GenericReportT l o m a -> GenericReportT l o m b -> GenericReportT l o m a #

Functor m => Functor (GenericReportT l o m) Source # 
Instance details

Defined in Control.OutputCapable.Blocks.Report.Generic

Methods

fmap :: (a -> b) -> GenericReportT l o m a -> GenericReportT l o m b #

(<$) :: a -> GenericReportT l o m b -> GenericReportT l o m a #

Monad m => Monad (GenericReportT l o m) Source # 
Instance details

Defined in Control.OutputCapable.Blocks.Report.Generic

Methods

(>>=) :: GenericReportT l o m a -> (a -> GenericReportT l o m b) -> GenericReportT l o m b #

(>>) :: GenericReportT l o m a -> GenericReportT l o m b -> GenericReportT l o m b #

return :: a -> GenericReportT l o m a #

MonadCatch m => MonadCatch (GenericReportT l o m) Source # 
Instance details

Defined in Control.OutputCapable.Blocks.Report.Generic

Methods

catch :: (HasCallStack, Exception e) => GenericReportT l o m a -> (e -> GenericReportT l o m a) -> GenericReportT l o m a #

MonadThrow m => MonadThrow (GenericReportT l o m) Source # 
Instance details

Defined in Control.OutputCapable.Blocks.Report.Generic

Methods

throwM :: (HasCallStack, Exception e) => e -> GenericReportT l o m a #

type Output l (GenericReportT l (IO ()) IO) Source # 
Instance details

Defined in Control.OutputCapable.Blocks

type Output l (GenericReportT l (IO ()) IO) = IO ()
type RunMonad l (GenericReportT l (IO ()) IO) Source # 
Instance details

Defined in Control.OutputCapable.Blocks

type RunMonad l (GenericReportT l (IO ()) IO) = IO

data Language Source #

Constructors

English 
German 

Instances

Instances details
Data Language Source # 
Instance details

Defined in Control.OutputCapable.Blocks.Report

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Language -> c Language #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Language #

toConstr :: Language -> Constr #

dataTypeOf :: Language -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Language) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Language) #

gmapT :: (forall b. Data b => b -> b) -> Language -> Language #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Language -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Language -> r #

gmapQ :: (forall d. Data d => d -> u) -> Language -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Language -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Language -> m Language #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Language -> m Language #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Language -> m Language #

Bounded Language Source # 
Instance details

Defined in Control.OutputCapable.Blocks.Report

Enum Language Source # 
Instance details

Defined in Control.OutputCapable.Blocks.Report

Generic Language Source # 
Instance details

Defined in Control.OutputCapable.Blocks.Report

Associated Types

type Rep Language 
Instance details

Defined in Control.OutputCapable.Blocks.Report

type Rep Language = D1 ('MetaData "Language" "Control.OutputCapable.Blocks.Report" "output-blocks-0.5.0.1-29ym9H8IG24SCC0fBh18M" 'False) (C1 ('MetaCons "English" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "German" 'PrefixI 'False) (U1 :: Type -> Type))

Methods

from :: Language -> Rep Language x #

to :: Rep Language x -> Language #

Read Language Source # 
Instance details

Defined in Control.OutputCapable.Blocks.Report

Show Language Source # 
Instance details

Defined in Control.OutputCapable.Blocks.Report

Eq Language Source # 
Instance details

Defined in Control.OutputCapable.Blocks.Report

Ord Language Source # 
Instance details

Defined in Control.OutputCapable.Blocks.Report

type Rep Language Source # 
Instance details

Defined in Control.OutputCapable.Blocks.Report

type Rep Language = D1 ('MetaData "Language" "Control.OutputCapable.Blocks.Report" "output-blocks-0.5.0.1-29ym9H8IG24SCC0fBh18M" 'False) (C1 ('MetaCons "English" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "German" 'PrefixI 'False) (U1 :: Type -> Type))

type Report o r = ReportT o Identity r Source #

getAllOuts :: Monad m => GenericReportT l o m () -> m [GenericOut l o] Source #

This is a more specific version of getAllOuts which enforces the usage pattern. You should always prefer this version over the generic.

toOutput :: GenericOut l o -> l -> o Source #

Monad for translations

newtype GenericLangM l (m :: Type -> Type) a Source #

Constructors

LangM 

Fields

Instances

Instances details
FunctorTrans (GenericLangM l) Source # 
Instance details

Defined in Control.OutputCapable.Blocks.Generic

Methods

lift :: Functor f => f a -> GenericLangM l f a Source #

Applicative m => Applicative (GenericLangM l m) Source # 
Instance details

Defined in Control.OutputCapable.Blocks.Generic

Methods

pure :: a -> GenericLangM l m a #

(<*>) :: GenericLangM l m (a -> b) -> GenericLangM l m a -> GenericLangM l m b #

liftA2 :: (a -> b -> c) -> GenericLangM l m a -> GenericLangM l m b -> GenericLangM l m c #

(*>) :: GenericLangM l m a -> GenericLangM l m b -> GenericLangM l m b #

(<*) :: GenericLangM l m a -> GenericLangM l m b -> GenericLangM l m a #

Functor m => Functor (GenericLangM l m) Source # 
Instance details

Defined in Control.OutputCapable.Blocks.Generic

Methods

fmap :: (a -> b) -> GenericLangM l m a -> GenericLangM l m b #

(<$) :: a -> GenericLangM l m b -> GenericLangM l m a #

type LangM' (m :: Type -> Type) a = GenericLangM Language m a Source #

type LangM (m :: Type -> Type) = LangM' m () Source #

type Rated (m :: Type -> Type) = LangM' m Rational Source #

Output monad

class (Applicative m, Ord l) => GenericOutputCapable l (m :: Type -> Type) where Source #

Methods

assertion :: Bool -> GenericLangM l m () -> GenericLangM l m () Source #

for assertions, i.e. expected behaviour is explanation (and abortion on False)

image :: FilePath -> GenericLangM l m () Source #

for printing a single image from file

images :: (k -> String) -> (a -> FilePath) -> Map k a -> GenericLangM l m () Source #

for printing multiple images using the given map

paragraph :: GenericLangM l m () -> GenericLangM l m () Source #

for a complete paragraph

refuse :: GenericLangM l m () -> GenericLangM l m () Source #

should abort at once

text :: String -> GenericLangM l m () Source #

for displaying text

enumerateM :: (a -> GenericLangM l m ()) -> [(a, GenericLangM l m ())] -> GenericLangM l m () Source #

for an enumerated sequence of elements

itemizeM :: [GenericLangM l m ()] -> GenericLangM l m () Source #

for an unenumerated sequence of elements

indent :: GenericLangM l m () -> GenericLangM l m () Source #

for indentation

latex :: String -> GenericLangM l m () Source #

for LaTeX-Math code (i.e. without surrounding $)

folded :: Bool -> (l -> String) -> GenericLangM l m () -> GenericLangM l m () Source #

for minimisable output with a default state (open/closed) and title

code :: String -> GenericLangM l m () Source #

for fixed width fonts (i.e. typewriter style)

translatedCode :: (l -> String) -> GenericLangM l m () Source #

same as code, but with different translations

translated :: (l -> String) -> GenericLangM l m () Source #

for displaying text with translations

Instances

Instances details
Ord l => GenericOutputCapable l Maybe Source # 
Instance details

Defined in Control.OutputCapable.Blocks.Generic

l ~ Language => GenericOutputCapable l (GenericReportT l (IO ()) IO) Source # 
Instance details

Defined in Control.OutputCapable.Blocks

Methods

assertion :: Bool -> GenericLangM l (GenericReportT l (IO ()) IO) () -> GenericLangM l (GenericReportT l (IO ()) IO) () Source #

image :: FilePath -> GenericLangM l (GenericReportT l (IO ()) IO) () Source #

images :: (k -> String) -> (a -> FilePath) -> Map k a -> GenericLangM l (GenericReportT l (IO ()) IO) () Source #

paragraph :: GenericLangM l (GenericReportT l (IO ()) IO) () -> GenericLangM l (GenericReportT l (IO ()) IO) () Source #

refuse :: GenericLangM l (GenericReportT l (IO ()) IO) () -> GenericLangM l (GenericReportT l (IO ()) IO) () Source #

text :: String -> GenericLangM l (GenericReportT l (IO ()) IO) () Source #

enumerateM :: (a -> GenericLangM l (GenericReportT l (IO ()) IO) ()) -> [(a, GenericLangM l (GenericReportT l (IO ()) IO) ())] -> GenericLangM l (GenericReportT l (IO ()) IO) () Source #

itemizeM :: [GenericLangM l (GenericReportT l (IO ()) IO) ()] -> GenericLangM l (GenericReportT l (IO ()) IO) () Source #

indent :: GenericLangM l (GenericReportT l (IO ()) IO) () -> GenericLangM l (GenericReportT l (IO ()) IO) () Source #

latex :: String -> GenericLangM l (GenericReportT l (IO ()) IO) () Source #

folded :: Bool -> (l -> String) -> GenericLangM l (GenericReportT l (IO ()) IO) () -> GenericLangM l (GenericReportT l (IO ()) IO) () Source #

code :: String -> GenericLangM l (GenericReportT l (IO ()) IO) () Source #

translatedCode :: (l -> String) -> GenericLangM l (GenericReportT l (IO ()) IO) () Source #

translated :: (l -> String) -> GenericLangM l (GenericReportT l (IO ()) IO) () Source #

(Bounded language, Enum language, Monad m, Ord language) => GenericOutputCapable language (GenericReportT language (GenericOutput language element) m) Source #

OutputCapable instances for GenericOutput, allowing for free conversion between ADT and interface.

Instance details

Defined in Control.OutputCapable.Blocks.Generic.Type

Methods

assertion :: Bool -> GenericLangM language (GenericReportT language (GenericOutput language element) m) () -> GenericLangM language (GenericReportT language (GenericOutput language element) m) () Source #

image :: FilePath -> GenericLangM language (GenericReportT language (GenericOutput language element) m) () Source #

images :: (k -> String) -> (a -> FilePath) -> Map k a -> GenericLangM language (GenericReportT language (GenericOutput language element) m) () Source #

paragraph :: GenericLangM language (GenericReportT language (GenericOutput language element) m) () -> GenericLangM language (GenericReportT language (GenericOutput language element) m) () Source #

refuse :: GenericLangM language (GenericReportT language (GenericOutput language element) m) () -> GenericLangM language (GenericReportT language (GenericOutput language element) m) () Source #

text :: String -> GenericLangM language (GenericReportT language (GenericOutput language element) m) () Source #

enumerateM :: (a -> GenericLangM language (GenericReportT language (GenericOutput language element) m) ()) -> [(a, GenericLangM language (GenericReportT language (GenericOutput language element) m) ())] -> GenericLangM language (GenericReportT language (GenericOutput language element) m) () Source #

itemizeM :: [GenericLangM language (GenericReportT language (GenericOutput language element) m) ()] -> GenericLangM language (GenericReportT language (GenericOutput language element) m) () Source #

indent :: GenericLangM language (GenericReportT language (GenericOutput language element) m) () -> GenericLangM language (GenericReportT language (GenericOutput language element) m) () Source #

latex :: String -> GenericLangM language (GenericReportT language (GenericOutput language element) m) () Source #

folded :: Bool -> (language -> String) -> GenericLangM language (GenericReportT language (GenericOutput language element) m) () -> GenericLangM language (GenericReportT language (GenericOutput language element) m) () Source #

code :: String -> GenericLangM language (GenericReportT language (GenericOutput language element) m) () Source #

translatedCode :: (language -> String) -> GenericLangM language (GenericReportT language (GenericOutput language element) m) () Source #

translated :: (language -> String) -> GenericLangM language (GenericReportT language (GenericOutput language element) m) () Source #

enumerate :: forall l (m :: Type -> Type) k a. GenericOutputCapable l m => (k -> String) -> (a -> String) -> Map k a -> GenericLangM l m () Source #

abortWith :: forall (m :: Type -> Type) o l. Monad m => o -> GenericLangM l (GenericReportT l o m) () Source #

alignOutput :: forall (m :: Type -> Type) o l. Monad m => ([o] -> o) -> GenericLangM l (GenericReportT l o m) () -> GenericLangM l (GenericReportT l o m) () Source #

This is a more specific version of alignOutput which enforces the usage pattern. You should always prefer this version over the generic.

combineReports :: forall (m :: Type -> Type) o l. Monad m => ([[o]] -> o) -> [GenericLangM l (GenericReportT l o m) ()] -> GenericLangM l (GenericReportT l o m) () Source #

This is a more specific version of combineReports which enforces the usage pattern. You should always prefer this version over the generic.

combineTwoReports :: forall (m :: Type -> Type) o l. Monad m => ([o] -> [o] -> o) -> GenericLangM l (GenericReportT l o m) () -> GenericLangM l (GenericReportT l o m) () -> GenericLangM l (GenericReportT l o m) () Source #

This is a more specific version of combineTwoReports which enforces the usage pattern. You should always prefer this version over the generic.

format :: forall (m :: Type -> Type) o l. Monad m => o -> GenericLangM l (GenericReportT l o m) () Source #

recoverFrom :: forall (m :: Type -> Type) l. Alternative m => GenericLangM l m () -> GenericLangM l m () Source #

recoverWith :: forall (m :: Type -> Type) a l b. Alternative m => a -> GenericLangM l m b -> GenericLangM l m (Either a b) Source #

toAbort :: forall (m :: Type -> Type) l o. Monad m => GenericLangM l (GenericReportT l o m) () -> GenericLangM l (GenericReportT l o m) () Source #

This is a more specific version of toAbort which enforces the usage pattern. You should always prefer this version over the generic.

Translation

data ArticleToUse Source #

Use the specified article.

Constructors

DefiniteArticle

use definite article(s)

IndefiniteArticle

use indefinite article(s)

Instances

Instances details
Data ArticleToUse Source # 
Instance details

Defined in Control.OutputCapable.Blocks

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ArticleToUse -> c ArticleToUse #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ArticleToUse #

toConstr :: ArticleToUse -> Constr #

dataTypeOf :: ArticleToUse -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ArticleToUse) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ArticleToUse) #

gmapT :: (forall b. Data b => b -> b) -> ArticleToUse -> ArticleToUse #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ArticleToUse -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ArticleToUse -> r #

gmapQ :: (forall d. Data d => d -> u) -> ArticleToUse -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ArticleToUse -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ArticleToUse -> m ArticleToUse #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ArticleToUse -> m ArticleToUse #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ArticleToUse -> m ArticleToUse #

Generic ArticleToUse Source # 
Instance details

Defined in Control.OutputCapable.Blocks

Associated Types

type Rep ArticleToUse 
Instance details

Defined in Control.OutputCapable.Blocks

type Rep ArticleToUse = D1 ('MetaData "ArticleToUse" "Control.OutputCapable.Blocks" "output-blocks-0.5.0.1-29ym9H8IG24SCC0fBh18M" 'False) (C1 ('MetaCons "DefiniteArticle" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "IndefiniteArticle" 'PrefixI 'False) (U1 :: Type -> Type))
Read ArticleToUse Source # 
Instance details

Defined in Control.OutputCapable.Blocks

Show ArticleToUse Source # 
Instance details

Defined in Control.OutputCapable.Blocks

Eq ArticleToUse Source # 
Instance details

Defined in Control.OutputCapable.Blocks

type Rep ArticleToUse Source # 
Instance details

Defined in Control.OutputCapable.Blocks

type Rep ArticleToUse = D1 ('MetaData "ArticleToUse" "Control.OutputCapable.Blocks" "output-blocks-0.5.0.1-29ym9H8IG24SCC0fBh18M" 'False) (C1 ('MetaCons "DefiniteArticle" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "IndefiniteArticle" 'PrefixI 'False) (U1 :: Type -> Type))

collapsed :: forall l (m :: Type -> Type). GenericOutputCapable l m => Bool -> State (Map l String) () -> GenericLangM l m () -> GenericLangM l m () Source #

This is a more specific version of collapsed which enforces the usage pattern. You should always prefer this version over the generic.

english :: String -> State (Map Language String) () Source #

Provide an English translation to be appended after previous English translations.

german :: String -> State (Map Language String) () Source #

Provide an German translation to be appended after previous German translations.

mapLangM :: (m a -> m b) -> GenericLangM l m a -> GenericLangM l m b Source #

multiLang :: forall (m :: Type -> Type). OutputCapable m => [(Language, String)] -> LangM m Source #

translate :: forall l (m :: Type -> Type). GenericOutputCapable l m => State (Map l String) () -> GenericLangM l m () Source #

This is a more specific version of translate which enforces the usage pattern. You should always prefer this version over the generic.

translateCode :: forall l (m :: Type -> Type). GenericOutputCapable l m => State (Map l String) () -> GenericLangM l m () Source #

This is a more specific version of translateCode which enforces the usage pattern. You should always prefer this version over the generic.

translations :: State (Map l a) () -> Map l a Source #

This is a more specific version of translations which enforces the usage pattern. You should always prefer this version over the generic.

Helper functions

newtype MinimumThreshold Source #

A Rational number indicating the minimal threshold.

newtype Punishment Source #

A Rational number indicating the punishment.

Constructors

Punishment 

newtype TargetedCorrect Source #

A Int number indicating expected correct answers.

Constructors

TargetedCorrect 

($=<<) :: Monad m => (a -> GenericLangM l m b) -> m a -> GenericLangM l m b infixr 0 Source #

extendedMultipleChoice Source #

Arguments

:: forall (m :: Type -> Type) a. (OutputCapable m, Ord a) 
=> MinimumThreshold

the minimum threshold of achieved points

-> Punishment

points to subtract per wrong answer

-> TargetedCorrect

how many correct answers have to be given within the submission in order to achieve full points

-> ArticleToUse

indicating if multiple different solutions could be possible

-> Map Language String

what is asked for

-> Maybe String

the correct solution to show

-> Map a Bool

possible answers and if they are correct

-> Map a Bool

the submission to evaluate

-> Rated m 

Evaluates multiple choice submissions by rejecting correctness below a minimum threshold.

The following preconditions need to hold before calling this function but are not checked:

  • targeted correct is at least one and not larger than the amount of possible answers

multipleChoice Source #

Arguments

:: forall (m :: Type -> Type) a. (OutputCapable m, Ord a) 
=> ArticleToUse

indicating if multiple different solutions could be possible

-> Map Language String

what is asked for

-> Maybe String

the correct solution to show

-> Map a Bool

possible answers and if they are correct

-> [a]

the submission to evaluate

-> Rated m 

Evaluates multiple choice submissions by rejecting correctness below 50 percent. (see extendedMultipleChoice)

multipleChoiceSyntax Source #

Arguments

:: forall (m :: Type -> Type) a. (OutputCapable m, Ord a, Show a) 
=> Bool

whether to continue after check (i.e. do not reject wrong answers)

-> [a]

possible answers

-> [a]

the submission to evaluate

-> LangM m 

Outputs feedback on syntax of a multiple choice submission. Depending on chosen parameters it might reject the submission.

printSolutionAndAssert Source #

Arguments

:: forall (m :: Type -> Type). OutputCapable m 
=> ArticleToUse

indicating if multiple different solutions could be possible

-> Maybe String

the correct solution to show

-> Rational

points achieved

-> Rated m 

Outputs the correct solution (if given) when achieved points are less than 100 percent. No points are distributed if not at least 50 percent are achieved. (see printSolutionAndAssertMinimum)

printSolutionAndAssertMinimum Source #

Arguments

:: forall (m :: Type -> Type). OutputCapable m 
=> MinimumThreshold

the minimum threshold of achieved points

-> ArticleToUse

indicating if multiple different solutions could be possible

-> Maybe String

the correct solution to show

-> Rational

points achieved

-> Rated m 

Outputs the correct solution (if given) when achieved points are less than 100 percent. No points are distributed if they do not reach the minimum threshold.

reRefuse :: forall (m :: Type -> Type). (Alternative m, Monad m, OutputCapable m) => Rated m -> LangM m -> Rated m Source #

Append some remarks after some rating function. But re-reject afterwards (if it was rejected by the rating function).

reRefuseLangM :: forall (m :: Type -> Type). (Alternative m, Monad m, OutputCapable m) => LangM m -> LangM m -> LangM m Source #

Append some remarks after a potential rejection. But re-reject afterwards (if it was rejected before).

Since: 0.4.0.3

singleChoice Source #

Arguments

:: forall (m :: Type -> Type) a. (OutputCapable m, Eq a) 
=> ArticleToUse

indicating if multiple different solutions could be possible

-> Map Language String

what is asked for

-> Maybe String

the correct solution to show

-> a

the correct answer

-> a

the submission to evaluate

-> LangM m 

Outputs feedback and rates a single choice submission.

singleChoiceSyntax Source #

Arguments

:: forall (m :: Type -> Type) a. (OutputCapable m, Eq a, Show a) 
=> Bool

whether to continue after check (i.e. do not reject wrong answers)

-> [a]

possible answers

-> a

the submission to evaluate

-> LangM m 

Outputs feedback on syntax of a single choice submission. Depending on chosen parameters it might reject the submission.

continueOrAbort :: forall (m :: Type -> Type). OutputCapable m => Bool -> Bool -> LangM m -> LangM m Source #

If argument is True, it will continue after assertion, otherwise it will stop if assertion fails.

yesNo :: forall (m :: Type -> Type). OutputCapable m => Bool -> LangM m -> LangM m Source #

In contrast to assertion it will only indicate that a check was performed and its result. However, it will not abort.

Orphan instances

l ~ Language => GenericOutputCapable l (GenericReportT l (IO ()) IO) Source # 
Instance details

Methods

assertion :: Bool -> GenericLangM l (GenericReportT l (IO ()) IO) () -> GenericLangM l (GenericReportT l (IO ()) IO) () Source #

image :: FilePath -> GenericLangM l (GenericReportT l (IO ()) IO) () Source #

images :: (k -> String) -> (a -> FilePath) -> Map k a -> GenericLangM l (GenericReportT l (IO ()) IO) () Source #

paragraph :: GenericLangM l (GenericReportT l (IO ()) IO) () -> GenericLangM l (GenericReportT l (IO ()) IO) () Source #

refuse :: GenericLangM l (GenericReportT l (IO ()) IO) () -> GenericLangM l (GenericReportT l (IO ()) IO) () Source #

text :: String -> GenericLangM l (GenericReportT l (IO ()) IO) () Source #

enumerateM :: (a -> GenericLangM l (GenericReportT l (IO ()) IO) ()) -> [(a, GenericLangM l (GenericReportT l (IO ()) IO) ())] -> GenericLangM l (GenericReportT l (IO ()) IO) () Source #

itemizeM :: [GenericLangM l (GenericReportT l (IO ()) IO) ()] -> GenericLangM l (GenericReportT l (IO ()) IO) () Source #

indent :: GenericLangM l (GenericReportT l (IO ()) IO) () -> GenericLangM l (GenericReportT l (IO ()) IO) () Source #

latex :: String -> GenericLangM l (GenericReportT l (IO ()) IO) () Source #

folded :: Bool -> (l -> String) -> GenericLangM l (GenericReportT l (IO ()) IO) () -> GenericLangM l (GenericReportT l (IO ()) IO) () Source #

code :: String -> GenericLangM l (GenericReportT l (IO ()) IO) () Source #

translatedCode :: (l -> String) -> GenericLangM l (GenericReportT l (IO ()) IO) () Source #

translated :: (l -> String) -> GenericLangM l (GenericReportT l (IO ()) IO) () Source #

l ~ Language => RunnableOutputCapable l (GenericReportT l (IO ()) IO) Source # 
Instance details

Associated Types

type RunMonad l (GenericReportT l (IO ()) IO) 
Instance details

Defined in Control.OutputCapable.Blocks

type RunMonad l (GenericReportT l (IO ()) IO) = IO
type Output l (GenericReportT l (IO ()) IO) 
Instance details

Defined in Control.OutputCapable.Blocks

type Output l (GenericReportT l (IO ()) IO) = IO ()

Methods

runLangM :: GenericLangM l (GenericReportT l (IO ()) IO) a -> RunMonad l (GenericReportT l (IO ()) IO) (Maybe a, l -> Output l (GenericReportT l (IO ()) IO)) Source #