Hi,

Using LambdaCase extension, you can write something quite elegant:

{-# LANGUAGE LambdaCase #-}

f :: Int -> IO String
f x = getDBRecord x >>= \case
    dbOutput
        | null dbOutput -> return "no db record"
        | otherwise      -> return "we got some db records"

Or better:

f :: Int -> IO String
f x = getDBRecord x >>= \case
          [] -> return "no db record"
          _  -> return "we got some db records"

But you can also use another function for the pure part:

recordMsg :: [a] -> String
recordMsg [] = "no db record"
recordMsg _ = "we got some db records"

f :: Int -> IO String
f = fmap recordMsg . getDBRecord

Regards,
Sylvain


2015-01-15 12:51 GMT+01:00 Miro Karpis <miroslav.karpis@gmail.com>:
Hi,

please is there a way to have guards with 'where' that communicates with IO? Or is there some other more elegant way? I can do this with classic if/else,...but I just find it nicer with guards.


I have something like this (just an example):


f :: Int -> IO String
f x
    | null dbOutput = return "no db record"
    | otherwise = return "we got some db records"
    where dbOutput = getDBRecord x


getDBRecord :: Int -> IO [Int]
getDBRecord recordId = do
    putStrLn $ "checking dbRecord" ++ show recordId
    --getting data from DB
    return [1,2]


problem is that db dbOutput is IO and the guard check does not like it:
 
Couldn't match expected type ‘[a0]’ with actual type ‘IO [Int]’
    In the first argument of ‘null’, namely ‘dbOutput’
    In the expression: null dbOutput



Cheers,
Miro

_______________________________________________
Beginners mailing list
Beginners@haskell.org
http://www.haskell.org/mailman/listinfo/beginners