[Maybe Int] sans Nothings

What's the best way to end up with a list composed of only the Just values,no Nothings? Michael ========================== import Control.Monad.Stateimport Data.Maybe type GeneratorState = State Int tick :: GeneratorState (Maybe Int)tick = do n <- get if ((n `mod` 7) == 0) then return Nothing else do put (n+1) return (Just n) {-*Main> evalState (sequence $ replicate 9 tick) 1[Just 1,Just 2,Just 3,Just 4,Just 5,Just 6,Nothing,Nothing,Nothing]-}

On 23 May 2011 17:20, michael rice
What's the best way to end up with a list composed of only the Just values, no Nothings?
http://haskell.org/hoogle/?hoogle=%3A%3A+%5BMaybe+a%5D+-%3E+%5Ba%5D
Data.Maybe.catMaybes is what you want :-) Cheers, Max

On 5/23/11 9:29 AM, Max Bolingbroke wrote:
On 23 May 2011 17:20, michael rice
mailto:nowgate@yahoo.com> wrote: What's the best way to end up with a list composed of only the Just values, no Nothings?
http://haskell.org/hoogle/?hoogle=%3A%3A+%5BMaybe+a%5D+-%3E+%5Ba%5D
Data.Maybe.catMaybes is what you want :-)
Cheers, Max
On 5/23/11 9:25 AM, Malcolm Wallace wrote:
On 23 May 2011, at 17:20, michael rice wrote:
What's the best way to end up with a list composed of only the Just values, no Nothings? Go to haskell.org/hoogle Type in "[Maybe a] -> [a]" Click on first result.
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
On 5/23/11 9:25 AM, Gregory Crosswhite wrote:
On 5/23/11 9:20 AM, michael rice wrote:
What's the best way to end up with a list composed of only the Just values, no Nothings?
Try catMaybes in Data.Maybe.
Cheers, Greg
GO TEAM HASKELL!!! Cheers, Greg

On 23 May 2011, at 17:20, michael rice wrote:
What's the best way to end up with a list composed of only the Just values, no Nothings?
Alternatively, [ x | Just x <- originals ] It also occurs to me that perhaps you still want the Just constructors. [ Just x | Just x <- originals ] [ x | x@(Just _) <- originals ]

Thanks, all.
Earlier, I was going to ask how to break out of a sequence op prematurely, i.e., you give it some replication number but want to break early if you get an end-flag value. While I was composing the post I thought of using Maybe for the good values and Nothing for the end value. Ergo, losing the Nothings at the end.
I was passing a map and an empty list into some state, but since the map doesn't change once it's created I moved it into a Reader. I was using the list to collect the elements but thought I can get that functionality automatically using sequence.
So, one thing leads to another. It's interesting how ideas begin bubbling up after one absorbs some critical mass of Haskell.
Michael
--- On Mon, 5/23/11, Malcolm Wallace
What's the best way to end up with a list composed of only the Just values, no Nothings?
Alternatively, [ x | Just x <- originals ] It also occurs to me that perhaps you still want the Just constructors. [ Just x | Just x <- originals ] [ x | x@(Just _) <- originals ] _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Mon, May 23, 2011 at 9:20 AM, michael rice
What's the best way to end up with a list composed of only the Just values, no Nothings?
Michael
==========================
import Control.Monad.State import Data.Maybe
type GeneratorState = State Int
tick :: GeneratorState (Maybe Int) tick = do n <- get if ((n `mod` 7) == 0) then return Nothing else do put (n+1) return (Just n)
{- *Main> evalState (sequence $ replicate 9 tick) 1 [Just 1,Just 2,Just 3,Just 4,Just 5,Just 6,Nothing,Nothing,Nothing] -}
There's a library function for it, but also:
filter ((/=) Nothing)
is readable enough.

On Mon, May 23, 2011 at 10:49:55AM -0700, Alexander Solla wrote:
On Mon, May 23, 2011 at 9:20 AM, michael rice
wrote: What's the best way to end up with a list composed of only the Just values, no Nothings?
Michael
==========================
import Control.Monad.State import Data.Maybe
type GeneratorState = State Int
tick :: GeneratorState (Maybe Int) tick = do n <- get if ((n `mod` 7) == 0) then return Nothing else do put (n+1) return (Just n)
{- *Main> evalState (sequence $ replicate 9 tick) 1 [Just 1,Just 2,Just 3,Just 4,Just 5,Just 6,Nothing,Nothing,Nothing] -}
There's a library function for it, but also:
filter ((/=) Nothing)
is readable enough.
Just a minor quibble: note that
filter (not . isNothing)
is slightly preferable since it does not introduce a frivolous equality constraint on the type wrapped by the Maybe. -Brent

Gregory Crosswhite
Or even better,
filter isJust
To make it worse again the original function can be generalized in a few ways. Here is a generalization from the inner Maybe type: import Data.Foldable as F catFoldables :: Foldable t => [t a] -> [a] catFoldables = concatMap F.toList Here is a generalization from the outer list type: joinMaybes :: (Alternative m, Monad m) => m (Maybe a) -> m a joinMaybes = (>>= maybe empty pure) And finally the generalization from everything: import Data.Foldable as F joinFoldables :: (Alternative m, Foldable t, Monad m) => m (t a) -> m a joinFoldables = (>>= F.foldr (\x _ -> pure x) empty) The final function looks a bit scary, but is actually surprisingly easy to understand, once you realize that 'foldr' is just a generalization of the 'maybe' function. The structure of Maybe is a list structure with at most one element after all. Greets, Ertugrul -- nightmare = unsafePerformIO (getWrongWife >>= sex) http://ertes.de/ -- nightmare = unsafePerformIO (getWrongWife >>= sex) http://ertes.de/

Brent Yorgey schrieb:
On Mon, May 23, 2011 at 10:49:55AM -0700, Alexander Solla wrote:
There's a library function for it, but also:
filter ((/=) Nothing) is readable enough.
Just a minor quibble: note that
filter (not . isNothing)
is slightly preferable since it does not introduce a frivolous equality constraint on the type wrapped by the Maybe.
Similar: http://www.haskell.org/haskellwiki/Haskell_programming_tips#Reduce_type_clas... http://www.haskell.org/haskellwiki/Haskell_programming_tips#Don.27t_ask_for_...

On 24/05/2011, at 5:49 AM, Alexander Solla wrote:
There's a library function for it, but also:
filter ((/=) Nothing)
The problem with that in general is that it only applies to [Maybe t] if Eq t, but you don't actually _need_ t to support equality. filter isJust will do the job, where isJust is in Data.Maybe.

On Mon, May 23, 2011 at 6:21 PM, Richard O'Keefe
On 24/05/2011, at 5:49 AM, Alexander Solla wrote:
There's a library function for it, but also:
filter ((/=) Nothing)
The problem with that in general is that it only applies to [Maybe t] if Eq t, but you don't actually _need_ t to support equality. filter isJust will do the job, where isJust is in Data.Maybe.
Indeed, isJust will do the job. Sometimes it is acceptable to just use the tools you know. For example, filtering a list of (Maybe Int)s. This is a balance that is tough to get right. Personally, I find non-functional values without Eq instances to be degenerate. So I really do not mind superfluous Eq constraints. I would not hesitate to use filter ((/=) Nothing) in a function whose type has no free type variables. It's just a bit of plumbing inside of a more complex function. But the point of avoiding unnecessary constraints is a good one, especially for constraints that constrain more strongly, e.g., Ord.

Alexander Solla schrieb:
Personally, I find non-functional values without Eq instances to be degenerate. So I really do not mind superfluous Eq constraints. I would not hesitate to use filter ((/=) Nothing) in a function whose type has no free type variables. It's just a bit of plumbing inside of a more complex function.
Sometimes it seems to be better to not allow Eq on Float and Double. Since most algebraic laws do not hold for those types, it is more often an error than an intention to compare two Float values. And how to compare (IO a) values? Also, by thinking about function types, you often get interesting use cases. Thus I would not assume too quickly that a type will always be instantiated by types other than a function type. Thus I would stick to (filter isJust) and use this consistently for monomorphic and polymorphic types.

Personally, I find non-functional values without Eq instances to be degenerate. So I really do not mind superfluous Eq constraints. I would not hesitate to use filter ((/=) Nothing) in a function whose type has no free type variables. It's just a bit of plumbing inside of a more complex function.
Sometimes it seems to be better to not allow Eq on Float and Double. Since most algebraic laws do not hold for those types, it is more often an error than an intention to compare two Float values. And how to compare (IO a) values?
Floats, Doubles, and IO are all "degenerate" types, for the reasons you outline. (Admittedly, Float and Double have Eq instances, but invalid Eq semantics) Notice how their value semantics each depend on the machine your runtime runs on, as opposed to merely the runtime. Bottom is another one of these degenerate types, since comparisons on arbitrary values are undecidable. Also, by thinking about function types, you often
get interesting use cases. Thus I would not assume too quickly that a type will always be instantiated by types other than a function type. Thus I would stick to (filter isJust) and use this consistently for monomorphic and polymorphic types.
I am not suggesting (filter ((/=) Nothing)) /over/ (filter isJust). Obviously, once one is aware of a better tool, one should use it. But I am suggesting that for simple cases which are unlikely to change in any substantive way, we should probably just use the tools we already know of, as opposed to searching for the "right" one. Both might involve costs. There is a cost involved in going to Google, thinking up a search term, finding that Data.Maybe has relevant functions, picking the right one. It takes less time to write "filter ..." than to type "haskell removing nothing from list", for example. When dealing with known unknowns, there is a balance to be made, and it is not easy. Michael's choice to ask the list imposed costs. (Not that we mind, we're all volunteers, after all). But it probably took 10 minutes to get the first reply. He could have written a bit of code that worked correctly, given the context of his problem, in 20 seconds. Then again, he probably worked on a different bit of code until somebody sent a solution, so we probably only have to account for the time spent in context switching, for everyone involved.

The input file: http://dl.dropbox.com/u/27842656/psalms
The Markov chain exercise from "The Practice of Programming", Kermighan/Pike. Sample runs at the end.
Michael
============================
import System.Environment(getArgs)import System.Randomimport Control.Applicativeimport Control.Monad.Readerimport Control.Monad.Stateimport Data.Maybeimport Data.Map
type Prefix = (String,String)type GeneratorState1 = State ((Map Prefix [String]),Prefix,[String])type GeneratorState2 = StateT (Prefix,StdGen) (Reader (Map Prefix [String]))
non_word = "\n"
f key new old = new ++ old
buildMap :: GeneratorState1 (Map Prefix [String])buildMap = do (mp,(pfx1,pfx2),words) <- get if (Prelude.null words) then {- No more words. Return final map (adding non_word for final prefix). -} return (insertWithKey' f (pfx1,pfx2) [non_word] mp) else do {- Add word to map at prefix & continue. -} put (insertWithKey' f (pfx1,pfx2) [head words] mp, (pfx2,(head words)), tail words) buildMap
generate :: GeneratorState2 (Maybe String)generate = do ((pfx1,pfx2),gen) <- get mp <- ask let suffixList = mp ! (pfx1,pfx2) let (index,newGen) = randomR (0, (length suffixList)-1) gen let word = suffixList !! index if (word == non_word) then return Nothing else do put ((pfx2,word),newGen) return (Just word)
rInt :: String -> IntrInt = read
main = do (seed:nwords:_) <- (Prelude.map rInt) <$> getArgs contents <- getContents putStrLn $ unwords $ catMaybes $ runReader (evalStateT (sequence $ replicate nwords generate) ((non_word,non_word),mkStdGen seed)) (evalState buildMap (singleton (non_word,non_word) [], (non_word,non_word), words contents))
{-[michael@hostname ~]$ ghc --make markov.hs[1 of 1] Compiling Main ( markov.hs, markov.o )Linking markov ...[michael@hostname ~]$ cat psalms | ./markov 111 100Blessed is the LORD, in thine own cause: remember how the foolish people have blasphemed thy name. In the courts of the righteous: The LORD taketh pleasure in the desert. And he led them with the wicked, and with the whole earth, is mount Zion, on the sides of thine only. O God, and was troubled: I complained, and my God. My times are in thy praise. Blessed be God, which is full of the LORD is good: for his wondrous works. Now also when I am small and despised: yet do I put my trust: how say ye to[michael@hostname ~]$ cat psalms | ./markov 666 100Blessed is the LORD, and cried unto thee, Thy face, LORD, will I remember thee from the beginning: and every one that is weaned of his heart to any wicked transgressors. Selah. They return at evening: they make ready their arrow upon the
people; and thou hast destroyed all them that fight against them that trust in thee: and let my tongue cleave to the heavens by his power for ever; and thy lovingkindnesses; for they have laid a snare before them: and that my ways were directed to keep thy word. Mine eyes fail while I have said that[michael@hostname ~]$
--- On Tue, 5/24/11, Alexander Solla
Personally, I find non-functional values without Eq instances to be
degenerate. So I really do not mind superfluous Eq constraints. I
would not hesitate to use filter ((/=) Nothing) in a function whose type
has no free type variables. It's just a bit of plumbing inside of a
more complex function.
Sometimes it seems to be better to not allow Eq on Float and Double. Since most algebraic laws do not hold for those types, it is more often an error than an intention to compare two Float values. And how to compare (IO a) values? Floats, Doubles, and IO are all "degenerate" types, for the reasons you outline. (Admittedly, Float and Double have Eq instances, but invalid Eq semantics) Notice how their value semantics each depend on the machine your runtime runs on, as opposed to merely the runtime. Bottom is another one of these degenerate types, since comparisons on arbitrary values are undecidable. Also, by thinking about function types, you often get interesting use cases. Thus I would not assume too quickly that a type will always be instantiated by types other than a function type. Thus I would stick to (filter isJust) and use this consistently for monomorphic and polymorphic types. I am not suggesting (filter ((/=) Nothing)) /over/ (filter isJust). Obviously, once one is aware of a better tool, one should use it. But I am suggesting that for simple cases which are unlikely to change in any substantive way, we should probably just use the tools we already know of, as opposed to searching for the "right" one. Both might involve costs. There is a cost involved in going to Google, thinking up a search term, finding that Data.Maybe has relevant functions, picking the right one. It takes less time to write "filter ..." than to type "haskell removing nothing from list", for example. When dealing with known unknowns, there is a balance to be made, and it is not easy. Michael's choice to ask the list imposed costs. (Not that we mind, we're all volunteers, after all). But it probably took 10 minutes to get the first reply. He could have written a bit of code that worked correctly, given the context of his problem, in 20 seconds. Then again, he probably worked on a different bit of code until somebody sent a solution, so we probably only have to account for the time spent in context switching, for everyone involved. -----Inline Attachment Follows----- _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

My comments are in-line, marked off with >>>
On Tue, May 24, 2011 at 4:09 PM, michael rice
The input file: http://dl.dropbox.com/u/27842656/psalms
The Markov chain exercise from "The Practice of Programming", Kermighan/Pike. Sample runs at the end.
Michael
============================
import System.Environment(getArgs) import System.Random import Control.Applicative import Control.Monad.Reader import Control.Monad.State import Data.Maybe import Data.Map
type Prefix = (String,String) type GeneratorState1 = State ((Map Prefix [String]),Prefix,[String]) type GeneratorState2 = StateT (Prefix,StdGen) (Reader (Map Prefix [String]))
non_word = "\n"
f key new old = new ++ old
I don't see what f is for, since it doesn't do anything with the key.
buildMap :: GeneratorState1 (Map Prefix [String]) buildMap = do (mp,(pfx1,pfx2),words) <- get if (Prelude.null words) then {- No more words. Return final map (adding non_word for final prefix). -} return (insertWithKey' f (pfx1,pfx2) [non_word] mp) else do {- Add word to map at prefix & continue. -} put (insertWithKey' f (pfx1,pfx2) [head words] mp, (pfx2,(head words)), tail words) buildMap
I'm not a fan of explicit if-then-else's, but my preferred alternative won't win much either. (see http://osdir.com/ml/haskell-cafe@haskell.org/2011-05/msg00612.html for an example of what I'm talking about)
generate :: GeneratorState2 (Maybe String) generate = do ((pfx1,pfx2),gen) <- get mp <- ask let suffixList = mp ! (pfx1,pfx2)
I'm not sure how you're guaranteed that mp ! (pfx1, pfx2) exists, at first glance. "lookup" uses Maybe semantics, in the case there is no result.
let (index,newGen) = randomR (0, (length suffixList)-1) gen
I might use a function like: listRange :: [a] -> (Int, Int) listRange list = (0, (length $ l) - 1) This is a common enough pattern to abstract away.
let word = suffixList !! index
if (word == non_word) then return Nothing else do put ((pfx2,word),newGen) return (Just word)
rInt :: String -> Int rInt = read
rInt is fair enough, but you can also have the same effect with an explicit type signature ((read n) :: Int) I tend to prefer the latter,
personally.
main = do (seed:nwords:_) <- (Prelude.map rInt) <$> getArgs contents <- getContents putStrLn $ unwords $ catMaybes $ runReader (evalStateT (sequence $ replicate nwords generate) ((non_word,non_word),mkStdGen seed)) (evalState buildMap (singleton (non_word,non_word) [], (non_word,non_word), words contents))
Nice use of functor application.
{- [michael@hostname ~]$ ghc --make markov.hs [1 of 1] Compiling Main ( markov.hs, markov.o ) Linking markov ... [michael@hostname ~]$ cat psalms | ./markov 111 100 Blessed is the LORD, in thine own cause: remember how the foolish people have blasphemed thy name. In the courts of the righteous: The LORD taketh pleasure in the desert. And he led them with the wicked, and with the whole earth, is mount Zion, on the sides of thine only. O God, and was troubled: I complained, and my God. My times are in thy praise. Blessed be God, which is full of the LORD is good: for his wondrous works. Now also when I am small and despised: yet do I put my trust: how say ye to [michael@hostname ~]$ cat psalms | ./markov 666 100 Blessed is the LORD, and cried unto thee, Thy face, LORD, will I remember thee from the beginning: and every one that is weaned of his heart to any wicked transgressors. Selah. They return at evening: they make ready their arrow upon the people; and thou hast destroyed all them that fight against them that trust in thee: and let my tongue cleave to the heavens by his power for ever; and thy lovingkindnesses; for they have laid a snare before them: and that my ways were directed to keep thy word. Mine eyes fail while I have said that [michael@hostname ~]$
--- On *Tue, 5/24/11, Alexander Solla
* wrote: From: Alexander Solla
Subject: Re: [Haskell-cafe] [Maybe Int] sans Nothings To: "Haskell Cafe" Date: Tuesday, May 24, 2011, 5:01 PM Personally, I find non-functional values without Eq instances to be degenerate. So I really do not mind superfluous Eq constraints. I would not hesitate to use filter ((/=) Nothing) in a function whose type has no free type variables. It's just a bit of plumbing inside of a more complex function.
Sometimes it seems to be better to not allow Eq on Float and Double. Since most algebraic laws do not hold for those types, it is more often an error than an intention to compare two Float values. And how to compare (IO a) values?
Floats, Doubles, and IO are all "degenerate" types, for the reasons you outline. (Admittedly, Float and Double have Eq instances, but invalid Eq semantics) Notice how their value semantics each depend on the machine your runtime runs on, as opposed to merely the runtime. Bottom is another one of these degenerate types, since comparisons on arbitrary values are undecidable.
Also, by thinking about function types, you often get interesting use cases. Thus I would not assume too quickly that a type will always be instantiated by types other than a function type. Thus I would stick to (filter isJust) and use this consistently for monomorphic and polymorphic types.
I am not suggesting (filter ((/=) Nothing)) /over/ (filter isJust). Obviously, once one is aware of a better tool, one should use it. But I am suggesting that for simple cases which are unlikely to change in any substantive way, we should probably just use the tools we already know of, as opposed to searching for the "right" one. Both might involve costs. There is a cost involved in going to Google, thinking up a search term, finding that Data.Maybe has relevant functions, picking the right one. It takes less time to write "filter ..." than to type "haskell removing nothing from list", for example. When dealing with known unknowns, there is a balance to be made, and it is not easy.
Michael's choice to ask the list imposed costs. (Not that we mind, we're all volunteers, after all). But it probably took 10 minutes to get the first reply. He could have written a bit of code that worked correctly, given the context of his problem, in 20 seconds. Then again, he probably worked on a different bit of code until somebody sent a solution, so we probably only have to account for the time spent in context switching, for everyone involved.
-----Inline Attachment Follows-----
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://mc/compose?to=Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Alexander Solla schrieb:
buildMap :: GeneratorState1 (Map Prefix [String]) buildMap = do (mp,(pfx1,pfx2),words) <- get if (Prelude.null words) then {- No more words. Return final map (adding non_word for final prefix). -} return (insertWithKey' f (pfx1,pfx2) [non_word] mp) else do {- Add word to map at prefix & continue. -} put (insertWithKey' f (pfx1,pfx2) [head words] mp, (pfx2,(head words)), tail words) buildMap
I'm not a fan of explicit if-then-else's, but my preferred
case words of [] -> {- no more words -} ... w:ws -> ... would work perfectly.

Yes, very nice. Thanks.
Michael
--- On Wed, 5/25/11, Henning Thielemann
buildMap :: GeneratorState1 (Map Prefix [String]) buildMap = do (mp,(pfx1,pfx2),words) <- get if (Prelude.null words) then {- No more words. Return final map (adding non_word for final prefix). -} return (insertWithKey' f (pfx1,pfx2) [non_word] mp) else do {- Add word to map at prefix & continue. -} put (insertWithKey' f (pfx1,pfx2) [head words] mp, (pfx2,(head words)), tail words) buildMap
I'm not a fan of explicit if-then-else's, but my preferred
case words of [] -> {- no more words -} ... w:ws -> ... would work perfectly.

Hi Michael,
You've used quite a few entirely redundant brackets. The tool HLint (
http://community.haskell.org/~ndm/hlint) will tell you which ones.
Thanks, Neil
On Wed, May 25, 2011 at 12:09 AM, michael rice
The input file: http://dl.dropbox.com/u/27842656/psalms
The Markov chain exercise from "The Practice of Programming", Kermighan/Pike. Sample runs at the end.
Michael
============================
import System.Environment(getArgs) import System.Random import Control.Applicative import Control.Monad.Reader import Control.Monad.State import Data.Maybe import Data.Map
type Prefix = (String,String) type GeneratorState1 = State ((Map Prefix [String]),Prefix,[String]) type GeneratorState2 = StateT (Prefix,StdGen) (Reader (Map Prefix [String]))
non_word = "\n"
f key new old = new ++ old
buildMap :: GeneratorState1 (Map Prefix [String]) buildMap = do (mp,(pfx1,pfx2),words) <- get if (Prelude.null words) then {- No more words. Return final map (adding non_word for final prefix). -} return (insertWithKey' f (pfx1,pfx2) [non_word] mp) else do {- Add word to map at prefix & continue. -} put (insertWithKey' f (pfx1,pfx2) [head words] mp, (pfx2,(head words)), tail words) buildMap
generate :: GeneratorState2 (Maybe String) generate = do ((pfx1,pfx2),gen) <- get mp <- ask let suffixList = mp ! (pfx1,pfx2) let (index,newGen) = randomR (0, (length suffixList)-1) gen let word = suffixList !! index if (word == non_word) then return Nothing else do put ((pfx2,word),newGen) return (Just word)
rInt :: String -> Int rInt = read
main = do (seed:nwords:_) <- (Prelude.map rInt) <$> getArgs contents <- getContents putStrLn $ unwords $ catMaybes $ runReader (evalStateT (sequence $ replicate nwords generate) ((non_word,non_word),mkStdGen seed)) (evalState buildMap (singleton (non_word,non_word) [], (non_word,non_word), words contents))
{- [michael@hostname ~]$ ghc --make markov.hs [1 of 1] Compiling Main ( markov.hs, markov.o ) Linking markov ... [michael@hostname ~]$ cat psalms | ./markov 111 100 Blessed is the LORD, in thine own cause: remember how the foolish people have blasphemed thy name. In the courts of the righteous: The LORD taketh pleasure in the desert. And he led them with the wicked, and with the whole earth, is mount Zion, on the sides of thine only. O God, and was troubled: I complained, and my God. My times are in thy praise. Blessed be God, which is full of the LORD is good: for his wondrous works. Now also when I am small and despised: yet do I put my trust: how say ye to [michael@hostname ~]$ cat psalms | ./markov 666 100 Blessed is the LORD, and cried unto thee, Thy face, LORD, will I remember thee from the beginning: and every one that is weaned of his heart to any wicked transgressors. Selah. They return at evening: they make ready their arrow upon the people; and thou hast destroyed all them that fight against them that trust in thee: and let my tongue cleave to the heavens by his power for ever; and thy lovingkindnesses; for they have laid a snare before them: and that my ways were directed to keep thy word. Mine eyes fail while I have said that [michael@hostname ~]$
--- On *Tue, 5/24/11, Alexander Solla
* wrote: From: Alexander Solla
Subject: Re: [Haskell-cafe] [Maybe Int] sans Nothings To: "Haskell Cafe" Date: Tuesday, May 24, 2011, 5:01 PM Personally, I find non-functional values without Eq instances to be degenerate. So I really do not mind superfluous Eq constraints. I would not hesitate to use filter ((/=) Nothing) in a function whose type has no free type variables. It's just a bit of plumbing inside of a more complex function.
Sometimes it seems to be better to not allow Eq on Float and Double. Since most algebraic laws do not hold for those types, it is more often an error than an intention to compare two Float values. And how to compare (IO a) values?
Floats, Doubles, and IO are all "degenerate" types, for the reasons you outline. (Admittedly, Float and Double have Eq instances, but invalid Eq semantics) Notice how their value semantics each depend on the machine your runtime runs on, as opposed to merely the runtime. Bottom is another one of these degenerate types, since comparisons on arbitrary values are undecidable.
Also, by thinking about function types, you often get interesting use cases. Thus I would not assume too quickly that a type will always be instantiated by types other than a function type. Thus I would stick to (filter isJust) and use this consistently for monomorphic and polymorphic types.
I am not suggesting (filter ((/=) Nothing)) /over/ (filter isJust). Obviously, once one is aware of a better tool, one should use it. But I am suggesting that for simple cases which are unlikely to change in any substantive way, we should probably just use the tools we already know of, as opposed to searching for the "right" one. Both might involve costs. There is a cost involved in going to Google, thinking up a search term, finding that Data.Maybe has relevant functions, picking the right one. It takes less time to write "filter ..." than to type "haskell removing nothing from list", for example. When dealing with known unknowns, there is a balance to be made, and it is not easy.
Michael's choice to ask the list imposed costs. (Not that we mind, we're all volunteers, after all). But it probably took 10 minutes to get the first reply. He could have written a bit of code that worked correctly, given the context of his problem, in 20 seconds. Then again, he probably worked on a different bit of code until somebody sent a solution, so we probably only have to account for the time spent in context switching, for everyone involved.
-----Inline Attachment Follows-----
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://mc/compose?to=Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Nice tool. I'll be using it a lot from now on, I'm sure. Thanks, Neil.
Michael
--- On Mon, 5/30/11, Neil Mitchell
Personally, I find non-functional values without Eq instances to be
degenerate. So I really do not mind superfluous Eq constraints. I
would not hesitate to use filter ((/=) Nothing) in a function whose type
has no free type variables. It's just a bit of plumbing inside of a
more complex function.
Sometimes it seems to be better to not allow Eq on Float and Double. Since most algebraic laws do not hold for those types, it is more often an error than an intention to compare two Float values. And how to compare (IO a) values? Floats, Doubles, and IO are all "degenerate" types, for the reasons you outline. (Admittedly, Float and Double have Eq instances, but invalid Eq semantics) Notice how their value semantics each depend on the machine your runtime runs on, as opposed to merely the runtime. Bottom is another one of these degenerate types, since comparisons on arbitrary values are undecidable. Also, by thinking about function types, you often get interesting use cases. Thus I would not assume too quickly that a type will always be instantiated by types other than a function type. Thus I would stick to (filter isJust) and use this consistently for monomorphic and polymorphic types. I am not suggesting (filter ((/=) Nothing)) /over/ (filter isJust). Obviously, once one is aware of a better tool, one should use it. But I am suggesting that for simple cases which are unlikely to change in any substantive way, we should probably just use the tools we already know of, as opposed to searching for the "right" one. Both might involve costs. There is a cost involved in going to Google, thinking up a search term, finding that Data.Maybe has relevant functions, picking the right one. It takes less time to write "filter ..." than to type "haskell removing nothing from list", for example. When dealing with known unknowns, there is a balance to be made, and it is not easy. Michael's choice to ask the list imposed costs. (Not that we mind, we're all volunteers, after all). But it probably took 10 minutes to get the first reply. He could have written a bit of code that worked correctly, given the context of his problem, in 20 seconds. Then again, he probably worked on a different bit of code until somebody sent a solution, so we probably only have to account for the time spent in context switching, for everyone involved. -----Inline Attachment Follows----- _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
participants (10)
-
Alexander Solla
-
Brent Yorgey
-
Ertugrul Soeylemez
-
Gregory Crosswhite
-
Henning Thielemann
-
Malcolm Wallace
-
Max Bolingbroke
-
michael rice
-
Neil Mitchell
-
Richard O'Keefe