Difference between revisions of "Case"

From HaskellWiki
Jump to navigation Jump to search
(moved from Hawiki)
 
(HaskellWiki syntax highlighting)
Line 1: Line 1:
Can I have a {{{case}}} where the alternatives contain expressions?
+
Can I have a <hask>case</hask> where the alternatives contain expressions?
   
   
You can make use of some SyntacticSugar of Haskell, namely of ["Guards"].
+
You can make use of some SyntacticSugar of Haskell, namely of [[Guards]].
   
{{{#!syntax haskell
+
<haskell>
 
case () of _
 
case () of _
 
| cond1 -> ex1
 
| cond1 -> ex1
Line 10: Line 10:
 
| cond3 -> ex3
 
| cond3 -> ex3
 
| otherwise -> exDefault
 
| otherwise -> exDefault
  +
</haskell>
}}}
 
   
 
Alternatively, one could simply factor out a function(/value) and use guards in the argument patterns.
 
Alternatively, one could simply factor out a function(/value) and use guards in the argument patterns.
   
 
Why sticking to syntactic sugar? We can do it nicely with a function implemented in Haskell:
 
Why sticking to syntactic sugar? We can do it nicely with a function implemented in Haskell:
{{{#!syntax haskell
+
<haskell>
 
select :: a -> [(Bool, a)] -> a
 
select :: a -> [(Bool, a)] -> a
 
select def = maybe def snd . List.find fst
 
select def = maybe def snd . List.find fst
Line 24: Line 24:
 
(cond2, ex2),
 
(cond2, ex2),
 
(cond3, ex3)]
 
(cond3, ex3)]
  +
</haskell>
}}}
 
   
 
Alternative implementations are
 
Alternative implementations are
{{{#!syntax haskell
+
<haskell>
 
select' def = fromMaybe def . lookup True
 
select' def = fromMaybe def . lookup True
   
Line 36: Line 36:
   
 
select'' = foldr (uncurry if')
 
select'' = foldr (uncurry if')
  +
</haskell>
}}}
 
The implementation of {{{select''}}} makes clear that {{{select}}} can be considered as nested {{{if}}}s.
+
The implementation of <hask>select''</hask> makes clear that <hask>select</hask> can be considered as nested <hask>if</hask>s.
The functional {{{if'}}} is also useful in connection with {{{zipWith3}}} since {{{zipWith3 if'}}} merges two lists according to a list of conditions.
+
The functional <hask>if'</hask> is also useful in connection with <hask>zipWith3</hask> since <hask>zipWith3 if'</hask> merges two lists according to a list of conditions.
   
   
 
If you don't like the parentheses for the pairs, you can also define
 
If you don't like the parentheses for the pairs, you can also define
{{{#!syntax haskell
+
<haskell>
 
data SelectBranch a = (:->) {
 
data SelectBranch a = (:->) {
 
condition :: Bool,
 
condition :: Bool,
Line 56: Line 56:
 
cond2 :-> ex2,
 
cond2 :-> ex2,
 
cond3 :-> ex3]
 
cond3 :-> ex3]
  +
</haskell>
}}}
 
  +
  +
[[Category::Idioms]]

Revision as of 15:04, 13 October 2006

Can I have a case where the alternatives contain expressions?


You can make use of some SyntacticSugar of Haskell, namely of Guards.

case () of _
             | cond1     -> ex1
             | cond2     -> ex2
             | cond3     -> ex3
             | otherwise -> exDefault

Alternatively, one could simply factor out a function(/value) and use guards in the argument patterns.

Why sticking to syntactic sugar? We can do it nicely with a function implemented in Haskell:

select :: a -> [(Bool, a)] -> a
select def = maybe def snd . List.find fst


select exDefault
    [(cond1, ex1),
     (cond2, ex2),
     (cond3, ex3)]

Alternative implementations are

select' def = fromMaybe def . lookup True

{- a purely functional implementation of if-then-else -}
if' :: Bool -> a -> a -> a
if' True  x _ = x
if' False _ y = y

select'' = foldr (uncurry if')

The implementation of select'' makes clear that select can be considered as nested ifs. The functional if' is also useful in connection with zipWith3 since zipWith3 if' merges two lists according to a list of conditions.


If you don't like the parentheses for the pairs, you can also define

data SelectBranch a = (:->) {
  condition  :: Bool,
  expression :: a
}

select :: a -> [SelectBranch a] -> a
select def = maybe def expression . List.find condition


select exDefault
    [cond1 :-> ex1,
     cond2 :-> ex2,
     cond3 :-> ex3]

[[Category::Idioms]]