Use the Identity monad to avoid unnecessary uses of fromJust

This commit is contained in:
Joseph C. Sible 2020-02-08 23:06:57 -05:00
parent 61b073d507
commit aaffe38198
4 changed files with 10 additions and 7 deletions

View file

@ -25,6 +25,7 @@ import Control.Monad.Writer
import Control.Monad
import Data.Char
import Data.Functor
import Data.Functor.Identity
import Data.List
import Data.Maybe
@ -177,7 +178,7 @@ getLiteralString = getLiteralStringExt (const Nothing)
-- Definitely get a literal string, skipping over all non-literals
onlyLiteralString :: Token -> String
onlyLiteralString = fromJust . getLiteralStringExt (const $ return "")
onlyLiteralString = runIdentity . getLiteralStringExt (const $ return "")
-- Maybe get a literal string, but only if it's an unquoted argument.
getUnquotedLiteral (T_NormalWord _ list) =
@ -216,7 +217,7 @@ getGlobOrLiteralString = getLiteralStringExt f
-- Maybe get the literal value of a token, using a custom function
-- to map unrecognized Tokens into strings.
getLiteralStringExt :: (Token -> Maybe String) -> Token -> Maybe String
getLiteralStringExt :: Monad m => (Token -> m String) -> Token -> m String
getLiteralStringExt more = g
where
allInList = fmap concat . mapM g