module Cheapskate.Types where
import Data.Sequence (Seq)
import Data.Default
import Data.Text (Text)
import qualified Data.Map as M
import Data.Data
import Control.DeepSeq (NFData(..))
import GHC.Generics (Generic)
data Doc = Doc Options Blocks
           deriving (Show, Data, Typeable)
data Block = Para Inlines
           | Header Int Inlines
           | Blockquote Blocks
           | List Bool ListType [Blocks]
           | CodeBlock CodeAttr Text
           | HtmlBlock Text
           | HRule
           deriving (Show, Data, Typeable)
data CodeAttr = CodeAttr { codeLang :: Text, codeInfo :: Text }
              deriving (Show, Data, Typeable)
data ListType = Bullet Char | Numbered NumWrapper Int deriving (Eq,Show,Data,Typeable)
data NumWrapper = PeriodFollowing | ParenFollowing deriving (Eq,Show,Data,Typeable)
data HtmlTagType = Opening Text | Closing Text | SelfClosing Text deriving (Show, Data, Typeable)
type Blocks = Seq Block
data Inline = Str Text
            | Space
            | SoftBreak
            | LineBreak
            | Emph Inlines
            | Strong Inlines
            | Code Text
            | Link Inlines Text  Text 
            | Image Inlines Text  Text 
            | Entity Text
            | RawHtml Text
            deriving (Show, Data, Typeable)
type Inlines = Seq Inline
type ReferenceMap = M.Map Text (Text, Text)
data Options = Options{
    sanitize           :: Bool  
  , allowRawHtml       :: Bool  
  , preserveHardBreaks :: Bool  
  , debug              :: Bool  
  }
  deriving (Show, Data, Typeable)
instance Default Options where
  def = Options{
          sanitize = True
        , allowRawHtml = True
        , preserveHardBreaks = False
        , debug = False
        }
deriving instance Generic Doc
instance NFData Doc
deriving instance Generic Block
instance NFData Block
deriving instance Generic CodeAttr
instance NFData CodeAttr
deriving instance Generic ListType
instance NFData ListType
deriving instance Generic NumWrapper
instance NFData NumWrapper
deriving instance Generic HtmlTagType
instance NFData HtmlTagType
deriving instance Generic Inline
instance NFData Inline
deriving instance Generic Options
instance NFData Options