Skip to content

Commit

Permalink
Fix incomplete patterns compiler warnings
Browse files Browse the repository at this point in the history
  • Loading branch information
MichelBoucey committed Oct 11, 2022
1 parent 372f946 commit 1704179
Show file tree
Hide file tree
Showing 2 changed files with 12 additions and 4 deletions.
6 changes: 5 additions & 1 deletion src/Text/Glabrous.hs
Original file line number Diff line number Diff line change
Expand Up @@ -161,7 +161,11 @@ fromTagsList ts = fromList $ (,T.empty) <$> ts

-- | Build an unset ad hoc 'Context' from the given 'Template'.
fromTemplate :: Template -> Context
fromTemplate t = setVariables ((\(Tag e) -> (e,T.empty)) <$> tagsOf t) initContext
fromTemplate t =
setVariables (toPair <$> tagsOf t) initContext
where
toPair (Tag e) = (e,T.empty)
toPair _ = undefined

-- | Get a 'Context' from a JSON file.
readContextFile :: FilePath -> IO (Maybe Context)
Expand Down
10 changes: 7 additions & 3 deletions src/Text/Glabrous/Types.hs
Original file line number Diff line number Diff line change
Expand Up @@ -6,7 +6,7 @@ module Text.Glabrous.Types where

import Data.Aeson
#if MIN_VERSION_aeson(2,0,0)
import qualified Data.Aeson.KeyMap as KM
import qualified Data.Aeson.KeyMap as KM
#endif
import qualified Data.HashMap.Strict as H
import qualified Data.Text as T
Expand Down Expand Up @@ -45,9 +45,9 @@ instance ToJSON Context where
instance FromJSON Context where
parseJSON (Object o) = return
#if MIN_VERSION_aeson(2,0,0)
Context { variables = H.fromList ((\(k,String v) -> (k,v)) <$> H.toList (KM.toHashMapText o)) }
Context { variables = H.fromList (fromJSONString <$> H.toList (KM.toHashMapText o)) }
#else
Context { variables = H.fromList ((\(k,String v) -> (k,v)) <$> H.toList o) }
Context { variables = H.fromList (fromJSONString <$> H.toList o) }
#endif
parseJSON _ = fail "expected an object"

Expand All @@ -56,3 +56,7 @@ data Result
| Partial { template :: !Template, context :: !Context }
deriving (Eq, Show)

fromJSONString :: (T.Text,Value) -> (T.Text,T.Text)
fromJSONString (k,String v) = (k,v)
fromJSONString (_,_) = undefined

0 comments on commit 1704179

Please sign in to comment.