> {-| > A subset of the GUI required to build a useful view > -} > module Frame.GUI ( > -- * GUI > GUI (..), > Composable (..), > Container (..), > Class, > URL, > Element (..), > Element' (..), > -- ** Forms > Label, > FormElement (..), > FormValue, > ) where > import Frame.Utilities > import Database.HaskellDB.DBLayout > import Frame.Types > class Composable a where > (<+) :: a -> Container -> a > (+>) :: Container -> a -> a > type Class = String > -- | A generic GUI whose various instances define how it should be output (e.g. Show outputs HTML). > data GUI > = Frame String [URL] [Container] -- ^ A frame with a title, some style and a set of containers > instance Composable GUI where > (Frame t s cs) <+ c = Frame t s $ cs ++ [c] > c +> (Frame t s cs) = Frame t s $ c:cs > instance Show GUI where > show (Frame t s cs) = "\n\t\n\t\t" ++ > t ++ "\n\t" ++ showCSS s ++ "\n" ++ > concatMap show cs ++ > "\n\t\n" > showCSS :: [String] -> String > showCSS [] = "" > showCSS (c:cs) = "\n\t\n\t" ++ showCSS cs > -- | Contains various 'block level' elements > data Container > = Panel [Container] [Class] -- ^ Panel matches up with a div when output as HTML > | Paragraph [Element] [Class] -- ^ Paragraphs can only only contain elements > | Code String -- ^ Code > | Quote [Container] -- ^ Quote > | Header Int [Element] -- ^ Header (int is size) > | List [[Container]] [Class] -- ^ Lists contain list items > | NumList [[Container]] [Class] -- ^ Lists contain list items > | Form [FormElement] [Class] -- ^ A form > | Error [Container]  -- ^ Error pane > | Line > | Empty > instance Composable Container where > (Panel cs s) <+ c = Panel (cs ++ [c]) s > (Quote cs) <+ c = Quote (cs ++ [c]) > (List css s) <+ c = List (css ++ [[c]]) s > (NumList css s) <+ c = NumList (css ++ [[c]]) s > (Error cs) <+ c = Error (cs ++ [c]) > c <+ c' = Panel (c:[c']) [] > c +> (Panel cs s) = Panel (c:cs) s > c +> (Quote cs) = Quote (c:cs) > c +> (List css s) = List ([c]:css) s > c +> (NumList css s) = NumList ([c]:css) s > c +> (Error cs) = Error (c:cs) > c' +> c = Panel (c:[c']) [] > instance Show Container where > show (Panel cs c) = "" ++ concatMap show cs ++ "" > show (Paragraph es c) = "" ++ concatMap show es ++ "

" > show (Code s) = "" ++ s ++ "" > show (Quote cs) = "
" ++ concatMap show cs ++ "
" > show (Header s es) = "" ++ concatMap show es ++ "" > show (List is c) = "" ++ concatMap showListItem is ++ "" > show (NumList is c) = "" ++ concatMap showListItem is ++ "" > show (Form fs c) = "" ++ concatMap show fs ++ "" > show (Error s) = "
" ++ concatMap show s ++ "
" > show Line = "
" > show Empty = "" > showClass :: [String] -> String > showClass [] = "" > showClass cs = " class=\"" ++ showClasses cs ++ "\"" > showClasses :: [String] -> String > showClasses [c] = c > showClasses (c:cs) = c ++ " " ++ showClasses cs > showListItem :: [Container] -> String > showListItem cs = "\n\t\t
  • " ++ concatMap show cs ++ "
  • " Some canonical types for URLs and Labels > -- | A URL > type URL = String > data Element > = Element Element' -- ^ Plain element > | Link URL Element' -- ^ Element wrapped in a link > | Strong [Element] -- ^ Element wrapped in a link > | Emphasis [Element] -- ^ Element wrapped in a link > | Break -- ^ Line break > instance Show Element where > show (Link u e) = "" ++ show e ++ "" > show (Strong es) = "" ++ concatMap show es ++ "" > show (Emphasis es) = "" ++ concatMap show es ++ "" > show (Element e) = show e > show Break = "
    " > data Element' > = Text String -- ^ Textual element > | Image URL String -- ^ Image element > instance Show Element' where > show (Image u s) = "\""" > show (Text s) = s > -- | A label > type Label = String > data FormElement > = FormGroup [FormElement] Label -- ^ For grouping elements > | TextField FieldName Label FormValue (Maybe Int) (Maybe Container) -- ^ Standard text box > | HiddenField FieldName FormValue -- ^ Hidden field > | TextArea FieldName Label FormValue (Maybe Container) -- ^ Larger text box > | Button FieldName FormValue -- ^ Submit button > | ButtonLink Label URL -- ^ Special textual button > instance Show FormElement where > show (FormGroup es l) = "
    " ++ ((length l == 0) ?? ("" ++ l ++ "")) ++ "
      " ++ concatMap show es ++ "
    " > show (TextField fn l fv ml (Just e)) = "
  • " ++ show e ++ "
  • " > show (TextField fn l fv ml Nothing) = "
  • " > show (HiddenField l fv) = "" > show (TextArea l t fv (Just e)) = "
  • " ++ show e ++ "
  • " > show (TextArea l t fv Nothing) = "
  • " > show (Button l fv) = "
  • " > show (ButtonLink l u) = "
  • " ++ l ++ "
  • " > showMaxLength :: Maybe Int -> String > showMaxLength (Just i) = " maxlength=\"" ++ show i ++ "\"" > showMaxLength Nothing = "" > -- | Form values are just wrapped types > type FormValue = WrapperType