Skip to content

Commit ddf1a39

Browse files
authored
Add Geolocation API (#1120)
Refactors all Navigator related utils into their own module. - [x] Adds `Miso.Navigator` module - [x] Consolidate all `navigator` related utilites into here - [x] Expose high-level `Effect` wrapper for `isOnline` - [x] Adds `geolocation` (based on `getCurrentPosition`)
1 parent f54c458 commit ddf1a39

File tree

4 files changed

+164
-57
lines changed

4 files changed

+164
-57
lines changed

miso.cabal

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -146,6 +146,7 @@ library
146146
Miso.Mathml.Element
147147
Miso.Mathml.Property
148148
Miso.Media
149+
Miso.Navigator
149150
Miso.Property
150151
Miso.PubSub
151152
Miso.Render

src/Miso/FFI/Internal.hs

Lines changed: 12 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -103,23 +103,22 @@ module Miso.FFI.Internal
103103
-- * Element
104104
, files
105105
, click
106-
-- * Clipboard
107-
, copyClipboard
108-
-- * Media
109-
, getUserMedia
110106
-- * WebSocket
111107
, websocketConnect
112108
, websocketClose
113109
, websocketSend
114110
-- * SSE
115111
, eventSourceConnect
116112
, eventSourceClose
117-
-- * Navigator
118-
, isOnLine
119113
-- * Blob
120114
, Blob (..)
121115
-- * ArrayBuffer
122116
, ArrayBuffer (..)
117+
-- * Navigator
118+
, geolocation
119+
, copyClipboard
120+
, getUserMedia
121+
, isOnLine
123122
) where
124123
-----------------------------------------------------------------------------
125124
import Control.Concurrent (ThreadId, forkIO)
@@ -817,3 +816,10 @@ newtype Blob = Blob JSVal
817816
newtype ArrayBuffer = ArrayBuffer JSVal
818817
deriving ToJSVal
819818
-----------------------------------------------------------------------------
819+
geolocation :: (JSVal -> JSM ()) -> (JSVal -> JSM ()) -> JSM ()
820+
geolocation successful errorful = do
821+
geo <- jsg "navigator" ! "geolocation"
822+
cb1 <- asyncCallback1 successful
823+
cb2 <- asyncCallback1 errorful
824+
void $ geo # "getCurrentPosition" $ (cb1, cb2)
825+
-----------------------------------------------------------------------------

src/Miso/Media.hs

Lines changed: 0 additions & 51 deletions
Original file line numberDiff line numberDiff line change
@@ -16,19 +16,15 @@ module Miso.Media
1616
Media (..)
1717
, NetworkState (..)
1818
, ReadyState (..)
19-
, UserMedia (..)
2019
, Stream
2120
-- *** Constructors
2221
, newAudio
23-
, userMedia
2422
-- *** Methods
2523
, canPlayType
2624
, load
2725
, play
2826
, pause
29-
, getUserMedia
3027
, srcObject
31-
, copyClipboard
3228
-- *** Properties
3329
, autoplay
3430
, controls
@@ -61,7 +57,6 @@ import qualified Language.Javascript.JSaddle as JS
6157
-----------------------------------------------------------------------------
6258
import qualified Miso.FFI.Internal as FFI
6359
import Miso.Event
64-
import Miso.Effect hiding ((<#))
6560
import Miso.String
6661
-----------------------------------------------------------------------------
6762
newtype Media = Media JSVal
@@ -204,55 +199,9 @@ videoWidth (Media m) = fromJSValUnchecked =<< m ! ("videoWidth" :: MisoString)
204199
volume :: Media -> JSM Double
205200
volume (Media m) = fromJSValUnchecked =<< m ! ("volume" :: MisoString)
206201
-----------------------------------------------------------------------------
207-
-- | Type for dealing with 'navigator.mediaDevices.getUserMedia'
208-
data UserMedia
209-
= UserMedia
210-
{ audio, video :: Bool
211-
} deriving (Show, Eq)
212-
-----------------------------------------------------------------------------
213-
-- | Default 'UserMedia'
214-
userMedia :: UserMedia
215-
userMedia = UserMedia True True
216-
-----------------------------------------------------------------------------
217202
type Stream = JSVal
218203
-----------------------------------------------------------------------------
219204
-- | Sets the `srcObject` on audio or video elements.
220205
srcObject :: Stream -> Media -> JSM ()
221206
srcObject stream (Media media) = media <# ("srcObject" :: MisoString) $ stream
222207
-----------------------------------------------------------------------------
223-
-- | Get access to user's media devices.
224-
--
225-
-- <https://developer.mozilla.org/en-US/docs/Web/API/MediaDevices/getUserMedia>
226-
--
227-
getUserMedia
228-
:: UserMedia
229-
-- ^ Options
230-
-> (Stream -> action)
231-
-- ^ Successful callback
232-
-> (JSVal -> action)
233-
-- ^ Errorful callback
234-
-> Effect parent model action
235-
getUserMedia UserMedia {..} successful errorful =
236-
withSink $ \sink ->
237-
FFI.getUserMedia audio video
238-
(sink . successful)
239-
(sink . errorful)
240-
-----------------------------------------------------------------------------
241-
-- | Get access to the user's clipboard.
242-
--
243-
-- <https://developer.mozilla.org/en-US/docs/Web/API/Navigator/clipboard>
244-
--
245-
copyClipboard
246-
:: MisoString
247-
-- ^ Options
248-
-> action
249-
-- ^ Successful callback
250-
-> (JSVal -> action)
251-
-- ^ Errorful callback
252-
-> Effect parent model action
253-
copyClipboard txt successful errorful =
254-
withSink $ \sink ->
255-
FFI.copyClipboard txt
256-
(sink successful)
257-
(sink . errorful)
258-
-----------------------------------------------------------------------------

src/Miso/Navigator.hs

Lines changed: 151 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,151 @@
1+
-----------------------------------------------------------------------------
2+
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
3+
{-# LANGUAGE ScopedTypeVariables #-}
4+
{-# LANGUAGE TypeApplications #-}
5+
{-# LANGUAGE RecordWildCards #-}
6+
{-# LANGUAGE ViewPatterns #-}
7+
{-# LANGUAGE LambdaCase #-}
8+
{-# LANGUAGE CPP #-}
9+
-----------------------------------------------------------------------------
10+
-- |
11+
-- Module : Miso.Navigator
12+
-- Copyright : (C) 2016-2025 David M. Johnson
13+
-- License : BSD3-style (see the file LICENSE)
14+
-- Maintainer : David M. Johnson <[email protected]>
15+
-- Stability : experimental
16+
-- Portability : non-portable
17+
----------------------------------------------------------------------------
18+
module Miso.Navigator
19+
( -- ** User media
20+
getUserMedia
21+
, userMedia
22+
, UserMedia (..)
23+
, Stream
24+
-- ** Clipboard
25+
, copyClipboard
26+
-- ** OnLine
27+
, isOnLine
28+
-- ** Geolocation
29+
, geolocation
30+
, Geolocation (..)
31+
, GeolocationError (..)
32+
) where
33+
-----------------------------------------------------------------------------
34+
import Control.Monad ((<=<))
35+
import Language.Javascript.JSaddle
36+
import Prelude hiding ((!!))
37+
-----------------------------------------------------------------------------
38+
import Miso.String
39+
import Miso.Effect
40+
import qualified Miso.FFI.Internal as FFI
41+
----------------------------------------------------------------------------
42+
type Stream = JSVal
43+
----------------------------------------------------------------------------
44+
-- | Get access to user's media devices.
45+
--
46+
-- <https://developer.mozilla.org/en-US/docs/Web/API/MediaDevices/getUserMedia>
47+
--
48+
getUserMedia
49+
:: UserMedia
50+
-- ^ Options
51+
-> (Stream -> action)
52+
-- ^ Successful callback
53+
-> (JSVal -> action)
54+
-- ^ Errorful callback
55+
-> Effect parent model action
56+
getUserMedia UserMedia {..} successful errorful =
57+
withSink $ \sink ->
58+
FFI.getUserMedia audio video
59+
(sink . successful)
60+
(sink . errorful)
61+
-----------------------------------------------------------------------------
62+
-- | Get access to the user's clipboard.
63+
--
64+
-- <https://developer.mozilla.org/en-US/docs/Web/API/Navigator/clipboard>
65+
--
66+
copyClipboard
67+
:: MisoString
68+
-- ^ Options
69+
-> action
70+
-- ^ Successful callback
71+
-> (JSVal -> action)
72+
-- ^ Errorful callback
73+
-> Effect parent model action
74+
copyClipboard txt successful errorful =
75+
withSink $ \sink ->
76+
FFI.copyClipboard txt
77+
(sink successful)
78+
(sink . errorful)
79+
-----------------------------------------------------------------------------
80+
-- | Get user's online status
81+
--
82+
-- <https://developer.mozilla.org/en-US/docs/Web/API/Navigator/onLine>
83+
--
84+
isOnLine
85+
:: (Bool -> action)
86+
-- ^ Successful callback
87+
-> Effect parent model action
88+
isOnLine action = io (action <$> FFI.isOnLine)
89+
-----------------------------------------------------------------------------
90+
-- | Type for dealing with 'navigator.mediaDevices.getUserMedia'
91+
--
92+
-- <https://developer.mozilla.org/en-US/docs/Web/API/Navigator/mediaDevices>
93+
--
94+
data UserMedia
95+
= UserMedia
96+
{ audio, video :: Bool
97+
} deriving (Show, Eq)
98+
-----------------------------------------------------------------------------
99+
-- | Default 'UserMedia'
100+
userMedia :: UserMedia
101+
userMedia = UserMedia True True
102+
-----------------------------------------------------------------------------
103+
-- | Geolocation fetching
104+
--
105+
-- <https://developer.mozilla.org/en-US/docs/Web/API/Navigator/geolocation>
106+
--
107+
geolocation
108+
:: (Geolocation -> action)
109+
-> (GeolocationError -> action)
110+
-> Effect parent model action
111+
geolocation successful errorful = do
112+
withSink $ \sink ->
113+
FFI.geolocation
114+
(sink . successful <=< fromJSValUnchecked)
115+
(sink . errorful <=< fromJSValUnchecked)
116+
-----------------------------------------------------------------------------
117+
data GeolocationError = GeolocationError GeolocationErrorCode MisoString
118+
deriving (Show, Eq)
119+
-----------------------------------------------------------------------------
120+
instance FromJSVal GeolocationError where
121+
fromJSVal v = do
122+
code <- fromJSVal =<< (v ! "code")
123+
msg <- fromJSVal =<< (v ! "message")
124+
pure (GeolocationError <$> code <*> msg)
125+
-----------------------------------------------------------------------------
126+
data GeolocationErrorCode
127+
= PERMISSION_DENIED
128+
| POSITION_UNAVAILABLE
129+
| TIMEOUT
130+
deriving (Enum, Show, Eq)
131+
-----------------------------------------------------------------------------
132+
instance FromJSVal GeolocationErrorCode where
133+
fromJSVal code =
134+
fromJSValUnchecked code >>= \case
135+
(1 :: Int) -> pure (Just PERMISSION_DENIED)
136+
2 -> pure (Just POSITION_UNAVAILABLE)
137+
3 -> pure (Just TIMEOUT)
138+
_ -> pure Nothing
139+
-----------------------------------------------------------------------------
140+
data Geolocation
141+
= Geolocation
142+
{ latitude, longitude, accuracy :: Double
143+
} deriving (Show, Eq)
144+
-----------------------------------------------------------------------------
145+
instance FromJSVal Geolocation where
146+
fromJSVal geo = do
147+
lat <- fromJSVal =<< geo ! "coords" ! "latitude"
148+
lon <- fromJSVal =<< geo ! "coords" ! "longitude"
149+
acc <- fromJSVal =<< geo ! "coords" ! "accuracy"
150+
pure (Geolocation <$> lat <*> lon <*> acc)
151+
-----------------------------------------------------------------------------

0 commit comments

Comments
 (0)