elm/compiler/src/Language/Elm.hs

83 lines
3 KiB
Haskell
Raw Normal View History

{-# LANGUAGE TypeSynonymInstances, FlexibleInstances #-}
{- | This module exports the functions necessary for compiling Elm code into the
2012-05-28 16:02:02 +00:00
respective HTML, JS and CSS code.
2012-05-30 19:49:46 +00:00
The type class @'ElmSource'@ requires an instance for all types that the Elm compiler
understands. The provided instances for String, Text and QuasiQuoted Elm source code
should be sufficient.
The documentation for the Elm language is available at <http://elm-lang.org/Documentation.elm>,
and many interactive examples are available at <http://elm-lang.org/Examples.elm>
2012-05-30 20:24:33 +00:00
Example implementations using Yesod and Happstack are available at <https://github.com/tazjin/Elm/tree/master/Examples>
2012-05-28 16:02:02 +00:00
-}
module Language.Elm (
2012-10-03 06:47:46 +00:00
ElmSource (..),
runtimeLocation
) where
2012-10-03 07:17:09 +00:00
import Data.Version (showVersion)
import CompileToJS
import ExtractNoscript
import GenerateHtml
import Initialize
import Text.Blaze.Html (Html)
import Language.Elm.Quasi
2012-10-03 06:47:46 +00:00
import Paths_Elm
2012-05-30 19:52:05 +00:00
import qualified Data.Text as TS
import qualified Data.Text.Lazy as TL
-- |The absolute path to Elm's runtime system.
runtimeLocation :: IO FilePath
runtimeLocation =
getDataFileName ("elm-runtime-" ++ showVersion version ++ ".js")
2012-10-03 06:47:46 +00:00
class ElmSource a where
-- |This function compiles Elm code to three separate parts: HTML, CSS,
-- and JavaScript. The HTML is only the contents of the body, so the three
-- parts must be combined in a basic HTML skeleton.
toParts :: a -> (Html, Html, String)
2012-05-30 19:49:46 +00:00
-- |This function compiles Elm code into a full HTML page.
toHtml :: String -- ^ Location of elm-min.js as expected by the browser
-> String -- ^ The page title
-> a -- ^ The elm source code
-> Html
instance ElmSource String where
toParts = toPartsHelper
toHtml = generateHtml
instance ElmSource Elm where
toParts = toPartsHelper . TL.unpack . renderElm
toHtml elmL title = generateHtml elmL title . TL.unpack . renderElm
2012-05-30 19:52:05 +00:00
-- |Strict text
instance ElmSource TS.Text where
toParts = toPartsHelper . TS.unpack
toHtml elmL title = generateHtml elmL title . TS.unpack
-- |Lazy text
instance ElmSource TL.Text where
toParts = toPartsHelper . TL.unpack
toHtml elmL title = generateHtml elmL title . TL.unpack
-- | (urlRenderFn, urlRenderFn -> Elm)
instance ElmSource (t, t -> Elm) where
toParts (f, s) = toPartsHelper $ TL.unpack $ renderElm $ s f
toHtml elmL title (f, s) = generateHtml elmL title $ TL.unpack $ renderElm $ s f
-- | to be used without URL interpolation
instance ElmSource (t -> Elm) where
toParts s = toPartsHelper $ TL.unpack $ renderElm $ s undefined
toHtml l t s = generateHtml l t $ TL.unpack $ renderElm $ s undefined
-- build helper to avoid boilerplate repetition
toPartsHelper :: String -> (Html, Html, String)
toPartsHelper source = (html, css, js)
2013-02-08 09:33:21 +00:00
where modul = buildFromSource source
js = either showErr jsModule modul
html = widgetBody $ either id extractNoscript modul