Problem spec from CareerCup.
Given two strings, return boolean True/False if they are only one edit apart. Edit can be insert/delete/update of only one character in the string. Eg.
-True
xyz,xz
xyz,xyk
xy,xyz
-False
xyz,xyz
xyz,xzy
x,xyz
module Strings.OneLetter where`
import Prelude
import qualified Data.Text as T`
oneLetter :: T.Text -> T.Text -> Bool
oneLetter s1 s2
  | s1 == s2 = False
  | max_l > (min_l + 1) = False
  | max_l == min_l = diff_size == 1
  | otherwise = diff_size == 0
  where
    length_s1 = T.length s1
    length_s2 = T.length s2
    max_l = max length_s1 length_s2
    min_l = min length_s1 length_s2
    diff_size = length $ filter (\(a,b) -> a /= b) zipped
    zipped = T.zip s1 s2`So, I used Text instead of String, hoping I could take advantage of fusion. I have the following questions and my initial attempt to answer them.
What is the time complexity of oneLetter
0(m+n) where m is the length of s1 and n is the length of s2
what is the space complexity of oneLetter?
I'm thinking due to laziness it's O(1), only two Chars are in memory at any one time, or two Ints.
 But I'm hazy on why. If this is wrong, please articulate why. If I'm 
right, and my reasoning is wrong or incomplete, please say why.
I don't think I can improve the time complexity. Am I right? Can the space complexity be improved?
What if I changed from Text to String?
I don't think the time complexity changes, but how does this change the space complexity?