remarks-0.1.13: A DSL for marking student work

Copyright(c) DIKU 2016-present
LicenseEUPLv1.1
Stabilityexperimental
Safe HaskellSafe
LanguageHaskell2010

Ast

Description

All .mrk files are parsed as a list of Judgements, as defined below.

Documentation

newtype Header Source #

Constructors

Header (String, Double, Double) 

Instances

Eq Header Source # 

Methods

(==) :: Header -> Header -> Bool #

(/=) :: Header -> Header -> Bool #

Show Header Source # 
Generic Header Source # 

Associated Types

type Rep Header :: * -> * #

Methods

from :: Header -> Rep Header x #

to :: Rep Header x -> Header #

Out Header Source # 

Methods

docPrec :: Int -> Header -> Doc #

doc :: Header -> Doc #

docList :: [Header] -> Doc #

type Rep Header Source # 
type Rep Header = D1 (MetaData "Header" "Ast" "remarks-0.1.13-GLibmXUYJsk3HaiilrVDg" True) (C1 (MetaCons "Header" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (String, Double, Double))))

data Mood Source #

Instances

Eq Mood Source # 

Methods

(==) :: Mood -> Mood -> Bool #

(/=) :: Mood -> Mood -> Bool #

Show Mood Source # 

Methods

showsPrec :: Int -> Mood -> ShowS #

show :: Mood -> String #

showList :: [Mood] -> ShowS #

Generic Mood Source # 

Associated Types

type Rep Mood :: * -> * #

Methods

from :: Mood -> Rep Mood x #

to :: Rep Mood x -> Mood #

Out Mood Source # 

Methods

docPrec :: Int -> Mood -> Doc #

doc :: Mood -> Doc #

docList :: [Mood] -> Doc #

type Rep Mood Source # 
type Rep Mood = D1 (MetaData "Mood" "Ast" "remarks-0.1.13-GLibmXUYJsk3HaiilrVDg" False) ((:+:) ((:+:) (C1 (MetaCons "Positive" PrefixI False) U1) (C1 (MetaCons "Negative" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Neutral" PrefixI False) U1) ((:+:) (C1 (MetaCons "Impartial" PrefixI False) U1) (C1 (MetaCons "Warning" PrefixI False) U1))))

newtype Comment Source #

Constructors

Comment (Mood, [CommentPart]) 

Instances

Eq Comment Source # 

Methods

(==) :: Comment -> Comment -> Bool #

(/=) :: Comment -> Comment -> Bool #

Show Comment Source # 
Generic Comment Source # 

Associated Types

type Rep Comment :: * -> * #

Methods

from :: Comment -> Rep Comment x #

to :: Rep Comment x -> Comment #

Out Comment Source # 

Methods

docPrec :: Int -> Comment -> Doc #

doc :: Comment -> Doc #

docList :: [Comment] -> Doc #

type Rep Comment Source # 
type Rep Comment = D1 (MetaData "Comment" "Ast" "remarks-0.1.13-GLibmXUYJsk3HaiilrVDg" True) (C1 (MetaCons "Comment" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Mood, [CommentPart]))))

newtype Property Source #

Constructors

Property (String, PropertyExp) 

Instances

Eq Property Source # 
Show Property Source # 
Generic Property Source # 

Associated Types

type Rep Property :: * -> * #

Methods

from :: Property -> Rep Property x #

to :: Rep Property x -> Property #

Out Property Source # 

Methods

docPrec :: Int -> Property -> Doc #

doc :: Property -> Doc #

docList :: [Property] -> Doc #

type Rep Property Source # 
type Rep Property = D1 (MetaData "Property" "Ast" "remarks-0.1.13-GLibmXUYJsk3HaiilrVDg" True) (C1 (MetaCons "Property" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (String, PropertyExp))))