diff --git a/README.md b/README.md index bb99a7de..da2282c9 100644 --- a/README.md +++ b/README.md @@ -361,7 +361,7 @@ updateModel SayHelloWorld m = m <# do viewModel :: Model -> View Action viewModel x = div_ [] [ button_ [ onClick AddOne ] [ text "+" ] - , text (show x) + , text $ toMisoString (show x) , button_ [ onClick SubtractOne ] [ text "-" ] ] ``` diff --git a/examples/compose-update/Main.hs b/examples/compose-update/Main.hs index 701a62fc..27981cfa 100644 --- a/examples/compose-update/Main.hs +++ b/examples/compose-update/Main.hs @@ -1,6 +1,7 @@ {-# LANGUAGE RankNTypes #-} {-# LANGUAGE RecordWildCards #-} {-# LANGUAGE TupleSections #-} +{-# LANGUAGE OverloadedStrings #-} module Main where -- This example demonstrates how you can split your update function @@ -13,6 +14,7 @@ import Data.Monoid import Miso import Miso.Lens +import Miso.String -- In this slightly contrived example, our model consists of two -- counters. When one of those counters is incremented, the other is @@ -100,6 +102,6 @@ viewModel (x, y) = div_ [] [ button_ [onClick Increment] [text "+"] - , text (show x <> " | " <> show y) + , text (ms (show x) <> " | " <> ms (show y)) , button_ [onClick Decrement] [text "-"] ] diff --git a/examples/haskell-miso.org/shared/Common.hs b/examples/haskell-miso.org/shared/Common.hs index 8e5287fa..4956977d 100644 --- a/examples/haskell-miso.org/shared/Common.hs +++ b/examples/haskell-miso.org/shared/Common.hs @@ -1,4 +1,5 @@ {-# LANGUAGE RecordWildCards #-} +{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeOperators #-} {-# LANGUAGE DataKinds #-} @@ -346,20 +347,20 @@ starMiso :: View action starMiso = a_ [ class_ (pack "github-button") , href_ (pack "https://github.com/dmjio/miso") - , prop (pack "data-icon") "octicon-star" - , prop (pack "data-size") "large" - , prop (pack "data-show-count") "true" - , prop (pack "aria-label") "Star dmjio/miso on GitHub" + , textProp (pack "data-icon") "octicon-star" + , textProp (pack "data-size") "large" + , textProp (pack "data-show-count") "true" + , textProp (pack "aria-label") "Star dmjio/miso on GitHub" ] [ text "Star" ] forkMiso :: View action forkMiso = a_ [ class_ (pack "github-button") , href_ (pack "https://github.com/dmjio/miso/fork") - , prop (pack "data-icon") "octicon-repo-forked" - , prop (pack "data-size") "large" - , prop (pack "data-show-count") "true" - , prop (pack "aria-label") "Fork dmjio/miso on GitHub" + , textProp (pack "data-icon") "octicon-repo-forked" + , textProp (pack "data-size") "large" + , textProp (pack "data-show-count") "true" + , textProp (pack "aria-label") "Fork dmjio/miso on GitHub" ] [ text "Fork" ] -- | Hero @@ -455,7 +456,7 @@ newNav = ] ] , div_ [ class_$pack "navbar-burger burger" - , prop (pack "data-target") (pack "navMenuIndex")] [ + , textProp (pack "data-target") (pack "navMenuIndex")] [ span_ [] [ ] ,span_ [] [ ] ,span_ [] [ ] @@ -518,7 +519,7 @@ newNav = ] , div_ [id_ $pack"blogDropdown" ,class_$pack "navbar-dropdown is-boxed" - ,prop (pack "data-style_") (pack "width: 18rem;")] [ + ,textProp (pack "data-style_") (pack "width: 18rem;")] [ a_ [class_$pack "navbar-item" ,href_$pack "/2017/07/24/access-previous-bulma-versions/"] [ div_ [class_$pack "navbar-content"] [ @@ -629,9 +630,9 @@ newNav = p_ [class_$pack "control"] [ a_ [ id_ $pack"twitter" , class_$pack "button" - , prop (pack "data-social-network_") (pack "Twitter") - , prop (pack "data-social-action_") (pack "tweet") - , prop (pack "data-social-target") (pack "http://bulma.io") + , textProp (pack "data-social-network_") (pack "Twitter") + , textProp (pack "data-social-action_") (pack "tweet") + , textProp (pack "data-social-target") (pack "http://bulma.io") ,target_$pack "_blank" , href_$pack "https://twitter.com/intent/tweet?text=Miso: a tasty Haskell front-end framework&url=https://haskell-miso.org&via=dmjio"] [ span_ [class_$pack "icon"] [ diff --git a/examples/router/Main.hs b/examples/router/Main.hs index ca8f62fc..22b078ca 100644 --- a/examples/router/Main.hs +++ b/examples/router/Main.hs @@ -1,4 +1,5 @@ {-# LANGUAGE ScopedTypeVariables #-} +{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE TypeOperators #-} {-# LANGUAGE DataKinds #-} {-# LANGUAGE RecordWildCards #-} diff --git a/examples/sse/shared/Common.hs b/examples/sse/shared/Common.hs index 1e92d755..f836cda5 100644 --- a/examples/sse/shared/Common.hs +++ b/examples/sse/shared/Common.hs @@ -1,9 +1,11 @@ +{-# LANGUAGE OverloadedStrings #-} module Common where import Data.Proxy import Servant.API import Miso +import Miso.String data Model = Model { modelUri :: URI, modelMsg :: String } deriving (Show, Eq) @@ -17,7 +19,7 @@ data Action home :: Model -> View Action home (Model _ msg) = - div_ [] [div_ [] [h3_ [] [text ("SSE (Server-sent events) Example" :: String)]], text msg] + div_ [] [div_ [] [h3_ [] [text "SSE (Server-sent events) Example"]], text $ ms msg] -- There is only a single route in this example type ClientRoutes = Home @@ -31,7 +33,7 @@ the404 :: View Action the404 = div_ [] - [ text ("404: Page not found") + [ text "404: Page not found" , a_ [onClick $ ChangeURI goHome] [text " - Go Home"] ] diff --git a/exe/Main.hs b/exe/Main.hs index 8b57beb3..5dac8e4b 100644 --- a/exe/Main.hs +++ b/exe/Main.hs @@ -1,7 +1,9 @@ +{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE RecordWildCards #-} module Main where import Miso +import Miso.String type Model = Int @@ -31,6 +33,7 @@ data Action viewModel :: Int -> View Action viewModel x = div_ [] [ button_ [ onClick AddOne ] [ text "+" ] - , text (show x) + , text $ ms (show x) , button_ [ onClick SubtractOne ] [ text "-" ] ] + diff --git a/ghc-src/Miso/Html/Internal.hs b/ghc-src/Miso/Html/Internal.hs index fd6057b2..7a09e0a9 100644 --- a/ghc-src/Miso/Html/Internal.hs +++ b/ghc-src/Miso/Html/Internal.hs @@ -132,8 +132,8 @@ node vNs vType vKey as xs = in View VNode {..} -- | `VText` creation -text :: ToMisoString str => str -> View action -text x = View $ VText (toMisoString x) +text :: MisoString -> View action +text = View . VText -- | Key for specific children patch newtype Key = Key MisoString diff --git a/ghc-src/Miso/String.hs b/ghc-src/Miso/String.hs index e00f6672..aa7c2ae9 100644 --- a/ghc-src/Miso/String.hs +++ b/ghc-src/Miso/String.hs @@ -13,12 +13,14 @@ module Miso.String ( ToMisoString (..) , MisoString + , module Data.Monoid , module Data.Text + , ms ) where -import Data.Aeson import qualified Data.ByteString as B import qualified Data.ByteString.Lazy as BL +import Data.Monoid import Data.Text import qualified Data.Text as T import qualified Data.Text.Encoding as T @@ -29,10 +31,15 @@ import qualified Data.Text.Lazy.Encoding as LT type MisoString = Text -- | Convenience class for creating `MisoString` from other string-like types -class ToMisoString str where toMisoString :: str -> MisoString +class ToMisoString str where + toMisoString :: str -> MisoString + +-- | Convenience function, shorthand for `toMisoString` +ms :: ToMisoString str => str -> MisoString +ms = toMisoString + instance ToMisoString MisoString where toMisoString = id instance ToMisoString String where toMisoString = T.pack instance ToMisoString LT.Text where toMisoString = LT.toStrict instance ToMisoString B.ByteString where toMisoString = toMisoString . T.decodeUtf8 instance ToMisoString BL.ByteString where toMisoString = toMisoString . LT.decodeUtf8 -instance ToMisoString Value where toMisoString = toMisoString . encode diff --git a/ghcjs-src/Miso/Html/Internal.hs b/ghcjs-src/Miso/Html/Internal.hs index cdd8a14e..a83b9507 100644 --- a/ghcjs-src/Miso/Html/Internal.hs +++ b/ghcjs-src/Miso/Html/Internal.hs @@ -142,11 +142,11 @@ data NS deriving (Show, Eq) -- | `VText` creation -text :: ToMisoString str => str -> View m +text :: MisoString -> View m text t = View . const $ do vtree <- create set "type" ("vtext" :: JSString) vtree - set "text" (toMisoString t) vtree + set "text" t vtree pure $ VTree vtree -- | For use with child reconciliaton algorithm diff --git a/ghcjs-src/Miso/String.hs b/ghcjs-src/Miso/String.hs index 4d2c913c..d10cee42 100644 --- a/ghcjs-src/Miso/String.hs +++ b/ghcjs-src/Miso/String.hs @@ -14,9 +14,11 @@ -- Portability : non-portable ---------------------------------------------------------------------------- module Miso.String ( - MisoString + ToMisoString (..) + , MisoString , module Data.JSString - , ToMisoString (..) + , module Data.Monoid + , ms ) where import Data.Aeson @@ -24,6 +26,7 @@ import qualified Data.ByteString as B import qualified Data.ByteString.Lazy as BL import Data.JSString import Data.JSString.Text +import Data.Monoid import qualified Data.Text as T import qualified Data.Text.Encoding as T import qualified Data.Text.Lazy as LT @@ -46,10 +49,13 @@ instance FromJSON MisoString where class ToMisoString str where toMisoString :: str -> MisoString +-- | Convenience function, shorthand for `toMisoString` +ms :: ToMisoString str => str -> MisoString +ms = toMisoString + instance ToMisoString MisoString where toMisoString = id instance ToMisoString String where toMisoString = pack instance ToMisoString T.Text where toMisoString = textToJSString instance ToMisoString LT.Text where toMisoString = lazyTextToJSString instance ToMisoString B.ByteString where toMisoString = toMisoString . T.decodeUtf8 instance ToMisoString BL.ByteString where toMisoString = toMisoString . LT.decodeUtf8 -instance ToMisoString Value where toMisoString = toMisoString . encode