diff --git a/src/ShellCheck/Analytics.hs b/src/ShellCheck/Analytics.hs
index 108682a..b7844dd 100644
--- a/src/ShellCheck/Analytics.hs
+++ b/src/ShellCheck/Analytics.hs
@@ -1443,14 +1443,14 @@ prop_checkConstantNullary5 = verify checkConstantNullary "[[ true ]]"
 prop_checkConstantNullary6 = verify checkConstantNullary "[ 1 ]"
 prop_checkConstantNullary7 = verify checkConstantNullary "[ false ]"
 checkConstantNullary _ (TC_Nullary _ _ t) | isConstant t =
-    case fromMaybe "" $ getLiteralString t of
+    case onlyLiteralString t of
         "false" -> err (getId t) 2158 "[ false ] is true. Remove the brackets."
         "0" -> err (getId t) 2159 "[ 0 ] is true. Use 'false' instead."
         "true" -> style (getId t) 2160 "Instead of '[ true ]', just use 'true'."
         "1" -> style (getId t) 2161 "Instead of '[ 1 ]', use 'true'."
         _ -> err (getId t) 2078 "This expression is constant. Did you forget a $ somewhere?"
   where
-    string = fromMaybe "" $ getLiteralString t
+    string = onlyLiteralString t
 
 checkConstantNullary _ _ = return ()
 
@@ -2276,7 +2276,7 @@ checkFunctionsUsedExternally params t =
             (Just str, t) -> do
                 let name = basename str
                 let args = skipOver t argv
-                let argStrings = map (\x -> (fromMaybe "" $ getLiteralString x, x)) args
+                let argStrings = map (\x -> (onlyLiteralString x, x)) args
                 let candidates = getPotentialCommands name argStrings
                 mapM_ (checkArg name (getId t)) candidates
             _ -> return ()
diff --git a/src/ShellCheck/Checks/Commands.hs b/src/ShellCheck/Checks/Commands.hs
index 8be60a7..86fda24 100644
--- a/src/ShellCheck/Checks/Commands.hs
+++ b/src/ShellCheck/Checks/Commands.hs
@@ -186,7 +186,7 @@ checkCommand map t@(T_SimpleCommand id cmdPrefix (cmd:rest)) = sequence_ $ do
             M.findWithDefault nullCheck (Basename $ basename name) map t
         else if name == "builtin" && not (null rest) then
             let t' = T_SimpleCommand id cmdPrefix rest
-                selectedBuiltin = fromMaybe "" $ getLiteralString . head $ rest
+                selectedBuiltin = onlyLiteralString $ head rest
             in M.findWithDefault nullCheck (Exactly selectedBuiltin) map t'
         else do
             M.findWithDefault nullCheck (Exactly name) map t
@@ -299,7 +299,7 @@ checkExpr = CommandCheck (Basename "expr") f where
                     "'expr' expects 3+ arguments but sees 1. Make sure each operator/operand is a separate argument, and escape <>&|."
 
             [first, second] |
-                (fromMaybe "" $ getLiteralString first) /= "length"
+                onlyLiteralString first /= "length"
                   && not (willSplit first || willSplit second) -> do
                     checkOp first
                     warn (getId t) 2307