Search code examples
haskelloption-typemorse-code

How to implement fromJust and iterate over a list of strings in Haskell


So I have got these functions:

intercalate' :: [a] -> [[a]] -> [a]
intercalate' xs xss = concat (intersperse' xs xss)

intersperse'             :: a -> [a] -> [a]
intersperse' _   []      = []
intersperse' sep (x:xs)  = x : prependToAll' sep xs

prependToAll'            :: a -> [a] -> [a]
prependToAll' _   []     = []
prependToAll' sep (x:xs) = sep : x : prependToAll' sep xs


encodeWord :: Table -> String -> Maybe Code
encodeWord table str = intercalate' [Silence, Silence]
    <$> mapM (\x -> lookup x table) str

for this data:

module Types where

data Atom = Beep | Silence
  deriving (Eq, Show)

type Code = [Atom]

dit, dah, shortGap, mediumGap :: Code
dit       = [Beep, Silence]
dah       = [Beep, Beep, Beep, Silence]
shortGap  = replicate (3-1) Silence
mediumGap = replicate (7-1) Silence

morseCode :: Char -> Code
morseCode 'A' = dit ++ dah
morseCode 'B' = dah ++ dit ++ dit ++ dit
morseCode 'C' = dah ++ dit ++ dah ++ dit
morseCode 'D' = dah ++ dit ++ dit
morseCode 'E' = dit
morseCode 'F' = dit ++ dit ++ dah ++ dit
morseCode 'G' = dah ++ dah ++ dit
morseCode 'H' = dit ++ dit ++ dit ++ dit
morseCode 'I' = dit ++ dit
morseCode 'J' = dit ++ dah ++ dah ++ dah
morseCode 'K' = dah ++ dit ++ dah
morseCode 'L' = dit ++ dah ++ dit ++ dit
morseCode 'M' = dah ++ dah
morseCode 'N' = dah ++ dit
morseCode 'O' = dah ++ dah ++ dah
morseCode 'P' = dit ++ dah ++ dah ++ dit
morseCode 'Q' = dah ++ dah ++ dit ++ dah
morseCode 'R' = dit ++ dah ++ dit
morseCode 'S' = dit ++ dit ++ dit
morseCode 'T' = dah
morseCode 'U' = dit ++ dit ++ dah
morseCode 'V' = dit ++ dit ++ dit ++ dah
morseCode 'W' = dit ++ dah ++ dah
morseCode 'X' = dah ++ dit ++ dit ++ dah
morseCode 'Y' = dah ++ dit ++ dah ++ dah
morseCode 'Z' = dah ++ dah ++ dit ++ dit
morseCode '1' = dit ++ dah ++ dah ++ dah ++ dah
morseCode '2' = dit ++ dit ++ dah ++ dah ++ dah
morseCode '3' = dit ++ dit ++ dit ++ dah ++ dah
morseCode '4' = dit ++ dit ++ dit ++ dit ++ dah
morseCode '5' = dit ++ dit ++ dit ++ dit ++ dit
morseCode '6' = dah ++ dit ++ dit ++ dit ++ dit
morseCode '7' = dah ++ dah ++ dit ++ dit ++ dit
morseCode '8' = dah ++ dah ++ dah ++ dit ++ dit
morseCode '9' = dah ++ dah ++ dah ++ dah ++ dit
morseCode '0' = dah ++ dah ++ dah ++ dah ++ dah
morseCode  _  = undefined -- Avoid warnings

type Table = [(Char, Code)]

morseTable :: Table
morseTable = [ (c , morseCode c) | c <- ['A'..'Z']++['0'..'9'] ]

The encodeWord function works as intended.

Sample: Input: "HELLO" Output: [Beep,Silence,Beep,Silence,Beep,Silence,Beep,Silence,Silence,Silence,Beep,Silence,Silence,Silence,Beep,Silence,Beep,Beep,Beep,Silence,Beep,Silence,Beep,Silence,Silence,Silence,Beep,Silence,Beep,Beep,Beep,Silence,Beep,Silence,Beep,Silence,Silence,Silence,Beep,Beep,Beep,Silence,Beep,Beep,Beep,Silence,Beep,Beep,Beep,Silence]

Now, I'm trying to define a new function: encodeWords.

Sample: Input: ["HI","THERE"] Output: [Beep,Silence,Beep,Silence,Beep,Silence,Beep,Silence,Silence,Silence,Beep,Silence,Beep,Silence,Silence,Silence,Silence,Silence,Silence,Silence,Beep,Beep,Beep,Silence,Silence,Silence,Beep,Silence,Beep,Silence,Beep,Silence,Beep,Silence,Silence,Silence,Beep,Silence,Silence,Silence,Beep,Silence,Beep,Beep,Beep,Silence,Beep,Silence,Silence,Silence,Beep,Silence]

So far, I have done this.

encodeWords :: Table -> [String] -> Maybe Code
encodeWords table stringList = intercalate' [Silence, Silence, Silence,Silence,Silence,Silence]
    <$> mapM (\x -> encodeWord table x ) stringList

I was hoping the final function would have the type signature:

Table -> [String] -> Code

For encodeWord, I have only managed to program Table -> [String] -> Maybe Code. I've tried using fromJust like this:

import Data.Maybe    
encodeWord :: Table -> String -> Code
encodeWord table str = fromJust (intercalate' [Silence, Silence]
    <$> mapM (\x -> lookup x table) str)

This worked, however, I can only use the Prelude and Data.Char for the program that I am writing.

When I tried:

fromJust          :: HasCallStack => Maybe a -> a
fromJust Nothing  = error "Maybe.fromJust: Nothing" -- yuck
fromJust (Just x) = x

type HasCallStack = (?callStack :: CallStack) 

encodeWord :: Table -> String -> Code
encodeWord table str = fromJust (intercalate' [Silence, Silence]
        <$> mapM (\x -> lookup x table) str)

I just got this error:

   Operator applied to too few arguments: ?
   |
59 | type HasCallStack = (?callStack :: CallStack)
   |                      ^
Failed, one module loaded.

Is there an easy way I can implement fromJust by myself, just using Data.Char and the Prelude ?

In summary, I'm trying to implement fromJust by myself and make this function work:

encodeWords :: Table -> [String] -> Maybe Code
encodeWords table stringList = intercalate' [Silence, Silence, Silence,Silence,Silence,Silence]
    <$> mapM (\x -> encodeWord table x ) stringList

I'm not sure if I should Map, MapM or something else to apply encodeWord to each of the strings in the list. After that, encodeWords should add 6 Silences between the output Code for each of the strings in the input list.


Solution

  • It is a perfectly workable error management policy to return Nothing if something is wrong, and you can cascade it.

    At the very end, you can always put the result thru fromJust and suffer the consequences if there is illegal input. As mentioned by HaskellFreak, your version of fromJust looks OK.

    This code seems to work:

    myFromJust :: Maybe a -> a
    myFromJust  Nothing   =  error "Maybe.fromJust: Nothing" -- yuck
    myFromJust  (Just x)  =  x
        
    encodeWord :: Table -> String -> Maybe Code
    encodeWord table str = (intercalate' [Silence, Silence]
                              <$> mapM (\x -> lookup x table) str)
    
    

    Testing under ghci:

     λ> 
     λ> encodeWord morseTable "ABC"
    Just [Beep,Silence,Beep,Beep,Beep,Silence,Silence,Silence,Beep,Beep,Beep,Silence,Beep,Silence,Beep,Silence,Beep,Silence,Silence,Silence,Beep,Beep,Beep,Silence,Beep,Silence,Beep,Beep,Beep,Silence,Beep,Silence]
     λ> 
     λ> 
     λ> encodeWord morseTable "ABC+"
     Nothing
     λ>
    

    Now trying to code the higher level function encodeWords:

    If we start with just a plain map construct:

     λ> 
     λ> stringList = ["ATTACK","AT","DAWN"]
     λ> 
     λ> :type (map (encodeWord morseTable) stringList)
     (map (encodeWord morseTable) stringList) :: [Maybe Code]
     λ>
    

    So we have a [Maybe Code] object. Given the type signature of intercalate', we would prefer a Maybe [Code] one.

     λ> 
     λ> :type mapM
    mapM :: (Traversable t, Monad m) => (a -> m b) -> t a -> m (t b)
     λ> 
    

    So if type a is the same as m b, and the leftmost function parameter is taken to be id, we see that mapM can swap the list construct with the Maybe one. Like in: (m b -> m b) -> t (m b) -> m (t b).

     λ> 
     λ> :type (mapM id)
    (mapM id) :: (Traversable t, Monad m) => t (m b) -> m (t b)
     λ> 
     λ> :type (mapM id $ map (encodeWord morseTable) stringList)
     (mapM id $ map (encodeWord morseTable) stringList) :: Maybe [Code]
     λ> 
     λ> 
     λ> sil6 = replicate 6 Silence
     λ> 
     λ> :type  ((intercalate' sil6) <$> mapM id (map (encodeWord morseTable) stringList))
      ((intercalate' sil6) <$> mapM id (map (encodeWord morseTable) stringList))
      :: Maybe [Atom]
     λ> 
    
    

    So this can be a valid code for encodeWords:

    encodeWords :: Table -> [String] -> Maybe Code
    encodeWords table stringList =
        let  sil6 = replicate 6 Silence
        in
             intercalate' sil6
                 <$>  (mapM id  $  map (encodeWord table) stringList)
    

    Testing under ghci:

     λ> 
     λ> length $ myFromJust (encodeWords morseTable stringList)
     112
     λ> (encodeWords morseTable stringList)
     Just [Beep,Silence,Beep,Beep,Beep,Silence,Silence,Silence,Beep,Beep,Beep,Silence,Silence,Silence,Beep,Beep,Beep,Silence,Silence,Silence,Beep,Silence,Beep,Beep,Beep,Silence,Silence,Silence,Beep,Beep,Beep,Silence,Beep,Silence,Beep,Beep,Beep,Silence,Beep,Silence,Silence,Silence,Beep,Beep,Beep,Silence,Beep,Silence,Beep,Beep,Beep,Silence,Silence,Silence,Silence,Silence,Silence,Silence,Beep,Silence,Beep,Beep,Beep,Silence,Silence,Silence,Beep,Beep,Beep,Silence,Silence,Silence,Silence,Silence,Silence,Silence,Beep,Beep,Beep,Silence,Beep,Silence,Beep,Silence,Silence,Silence,Beep,Silence,Beep,Beep,Beep,Silence,Silence,Silence,Beep,Silence,Beep,Beep,Beep,Silence,Beep,Beep,Beep,Silence,Silence,Silence,Beep,Beep,Beep,Silence,Beep,Silence]
     λ> 
    
    

    Note that in that context, mapM id is the same thing as library function sequence :: Monad m => t (m a) -> m (t a), which is definitely in the Prelude set.

    In the interest of full disclosure, the Prelude library also includes a traverse function, which is kind of a dalliance between sequence and map. So you can write a slightly more elegant version of encodeWords like this:

    encodeWords2 :: Table -> [String] -> Maybe Code
    encodeWords2 table stringList =
        let  sil6 = replicate 6 Silence
        in   intercalate' sil6  <$>  traverse (encodeWord table) stringList