Skip to content

Commit

Permalink
Merge pull request #234 from haskell-miso/string-fixes
Browse files Browse the repository at this point in the history
Remove ToMisoString constraint on text
  • Loading branch information
dmjio authored Aug 4, 2017
2 parents a68152a + b7d5c6a commit 4d91059
Show file tree
Hide file tree
Showing 10 changed files with 50 additions and 28 deletions.
2 changes: 1 addition & 1 deletion README.md
Original file line number Diff line number Diff line change
Expand Up @@ -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 "-" ]
]
```
Expand Down
4 changes: 3 additions & 1 deletion examples/compose-update/Main.hs
Original file line number Diff line number Diff line change
@@ -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
Expand All @@ -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
Expand Down Expand Up @@ -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 "-"]
]
27 changes: 14 additions & 13 deletions examples/haskell-miso.org/shared/Common.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,5 @@
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE DataKinds #-}
Expand Down Expand Up @@ -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
Expand Down Expand Up @@ -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_ [] [ ]
Expand Down Expand Up @@ -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"] [
Expand Down Expand Up @@ -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"] [
Expand Down
1 change: 1 addition & 0 deletions examples/router/Main.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,5 @@
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE RecordWildCards #-}
Expand Down
6 changes: 4 additions & 2 deletions examples/sse/shared/Common.hs
Original file line number Diff line number Diff line change
@@ -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)
Expand All @@ -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
Expand All @@ -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"]
]

Expand Down
5 changes: 4 additions & 1 deletion exe/Main.hs
Original file line number Diff line number Diff line change
@@ -1,7 +1,9 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
module Main where

import Miso
import Miso.String

type Model = Int

Expand Down Expand Up @@ -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 "-" ]
]

4 changes: 2 additions & 2 deletions ghc-src/Miso/Html/Internal.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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
Expand Down
13 changes: 10 additions & 3 deletions ghc-src/Miso/String.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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
Expand All @@ -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
4 changes: 2 additions & 2 deletions ghcjs-src/Miso/Html/Internal.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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
Expand Down
12 changes: 9 additions & 3 deletions ghcjs-src/Miso/String.hs
Original file line number Diff line number Diff line change
Expand Up @@ -14,16 +14,19 @@
-- Portability : non-portable
----------------------------------------------------------------------------
module Miso.String (
MisoString
ToMisoString (..)
, MisoString
, module Data.JSString
, ToMisoString (..)
, module Data.Monoid
, ms
) where

import Data.Aeson
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
Expand All @@ -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

0 comments on commit 4d91059

Please sign in to comment.