
i'm trying to create my own split function with % as delimiter. so i have eqD = (=='%') and send let s = "zaoeu%aeuasnt%staashaeu%nthdanoe%nthd" putStrLn $ show $ brS (findIndex eqD s) s to a function brS: brS i ss | isNothing i = ss | otherwise = (take i ss) : (brS newIndex newStr) where newIndex = findIndex eqD newStr newStr = drop (i+1) ss but get the following error: Couldn't match expected type `Maybe a' against inferred type `Int' In the first argument of `isNothing', namely `i' In the expression: isNothing i :: mayBe a In a stmt of a pattern guard for the definition of `brS': isNothing i :: mayBe a my understanding is that i need the isNothing because findIndex will return Just Int or Nothing. however, i'm not sure how to resolve what seems to me to be an issue between a Maybe and an Int. -- In friendship, prad ... with you on your journey Towards Freedom http://www.towardsfreedom.com (website) Information, Inspiration, Imagination - truly a site for soaring I's

This is happening because findIndex has the signature: findIndexhttp://hackage.haskell.org/packages/archive/haskell98/latest/doc/html/List.h...:: (a -> Bool) -> [a] -> Maybe Int
From this we know that 'findIndex' can return a 'Just Int' or 'Nothing'.
GHC is telling you that you need to handle the case where the list element
you ask for does not exist and findIndex returns 'Nothing'.
The functions in the Maybe module [1]may be of some help here.
-deech
[1]
http://hackage.haskell.org/packages/archive/haskell98/latest/doc/html/Maybe....
On Thu, Aug 5, 2010 at 5:22 PM, prad
i'm trying to create my own split function with % as delimiter. so i have eqD = (=='%')
and send
let s = "zaoeu%aeuasnt%staashaeu%nthdanoe%nthd" putStrLn $ show $ brS (findIndex eqD s) s
to a function brS:
brS i ss | isNothing i = ss | otherwise = (take i ss) : (brS newIndex newStr) where newIndex = findIndex eqD newStr newStr = drop (i+1) ss
but get the following error:
Couldn't match expected type `Maybe a' against inferred type `Int' In the first argument of `isNothing', namely `i' In the expression: isNothing i :: mayBe a In a stmt of a pattern guard for the definition of `brS': isNothing i :: mayBe a
my understanding is that i need the isNothing because findIndex will return Just Int or Nothing.
however, i'm not sure how to resolve what seems to me to be an issue between a Maybe and an Int.
-- In friendship, prad
... with you on your journey Towards Freedom http://www.towardsfreedom.com (website) Information, Inspiration, Imagination - truly a site for soaring I's _______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

Sorry didn't read that properly. Hold on.
-deech
On Thu, Aug 5, 2010 at 5:31 PM, aditya siram
This is happening because findIndex has the signature: findIndexhttp://hackage.haskell.org/packages/archive/haskell98/latest/doc/html/List.h...:: (a -> Bool) -> [a] -> Maybe Int
From this we know that 'findIndex' can return a 'Just Int' or 'Nothing'.
GHC is telling you that you need to handle the case where the list element you ask for does not exist and findIndex returns 'Nothing'.
The functions in the Maybe module [1]may be of some help here.
-deech
[1] http://hackage.haskell.org/packages/archive/haskell98/latest/doc/html/Maybe....
On Thu, Aug 5, 2010 at 5:22 PM, prad
wrote: i'm trying to create my own split function with % as delimiter. so i have eqD = (=='%')
and send
let s = "zaoeu%aeuasnt%staashaeu%nthdanoe%nthd" putStrLn $ show $ brS (findIndex eqD s) s
to a function brS:
brS i ss | isNothing i = ss | otherwise = (take i ss) : (brS newIndex newStr) where newIndex = findIndex eqD newStr newStr = drop (i+1) ss
but get the following error:
Couldn't match expected type `Maybe a' against inferred type `Int' In the first argument of `isNothing', namely `i' In the expression: isNothing i :: mayBe a In a stmt of a pattern guard for the definition of `brS': isNothing i :: mayBe a
my understanding is that i need the isNothing because findIndex will return Just Int or Nothing.
however, i'm not sure how to resolve what seems to me to be an issue between a Maybe and an Int.
-- In friendship, prad
... with you on your journey Towards Freedom http://www.towardsfreedom.com (website) Information, Inspiration, Imagination - truly a site for soaring I's _______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

The problem was the use of 'i' in 'take' and drop both of which require a
Int. Here is code that corrects that:
import Data.List
import Data.Maybe
eqD = (=='%')
test4 = let s = "zaoeu%aeuasnt%staashaeu%nthdanoe%nthd" in
putStrLn $ show $ brS (findIndex eqD s) s
brS :: Maybe Int -> String -> String
brS i ss
| isNothing i = ss
| otherwise = (take (fromJust i) ss) ++ (brS newIndex newStr)
where
newIndex = findIndex eqD newStr
newStr = drop ((fromJust i) +1) ss
-deech
On Thu, Aug 5, 2010 at 5:32 PM, aditya siram
Sorry didn't read that properly. Hold on. -deech
On Thu, Aug 5, 2010 at 5:31 PM, aditya siram
wrote: This is happening because findIndex has the signature: findIndexhttp://hackage.haskell.org/packages/archive/haskell98/latest/doc/html/List.h...:: (a -> Bool) -> [a] -> Maybe Int
From this we know that 'findIndex' can return a 'Just Int' or 'Nothing'.
GHC is telling you that you need to handle the case where the list element you ask for does not exist and findIndex returns 'Nothing'.
The functions in the Maybe module [1]may be of some help here.
-deech
[1] http://hackage.haskell.org/packages/archive/haskell98/latest/doc/html/Maybe....
On Thu, Aug 5, 2010 at 5:22 PM, prad
wrote: i'm trying to create my own split function with % as delimiter. so i have eqD = (=='%')
and send
let s = "zaoeu%aeuasnt%staashaeu%nthdanoe%nthd" putStrLn $ show $ brS (findIndex eqD s) s
to a function brS:
brS i ss | isNothing i = ss | otherwise = (take i ss) : (brS newIndex newStr) where newIndex = findIndex eqD newStr newStr = drop (i+1) ss
but get the following error:
Couldn't match expected type `Maybe a' against inferred type `Int' In the first argument of `isNothing', namely `i' In the expression: isNothing i :: mayBe a In a stmt of a pattern guard for the definition of `brS': isNothing i :: mayBe a
my understanding is that i need the isNothing because findIndex will return Just Int or Nothing.
however, i'm not sure how to resolve what seems to me to be an issue between a Maybe and an Int.
-- In friendship, prad
... with you on your journey Towards Freedom http://www.towardsfreedom.com (website) Information, Inspiration, Imagination - truly a site for soaring I's _______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

On Thu, Aug 05, 2010 at 05:42:40PM -0500, aditya siram wrote:
brS :: Maybe Int -> String -> String brS i ss | isNothing i = ss | otherwise = (take (fromJust i) ss) ++ (brS newIndex newStr) where newIndex = findIndex eqD newStr newStr = drop ((fromJust i) +1) ss
/me makes deech write on the blackboard 100 times, "I will not use fromJust"

Normally yes, but here we are guaranteed to get a 'Just ...' value because
of the 'isNothing' guard.
-deech
On Thu, Aug 5, 2010 at 5:47 PM, Brent Yorgey
On Thu, Aug 05, 2010 at 05:42:40PM -0500, aditya siram wrote:
brS :: Maybe Int -> String -> String brS i ss | isNothing i = ss | otherwise = (take (fromJust i) ss) ++ (brS newIndex newStr) where newIndex = findIndex eqD newStr newStr = drop ((fromJust i) +1) ss
/me makes deech write on the blackboard 100 times, "I will not use fromJust" _______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

On Thu, Aug 05, 2010 at 06:20:06PM -0500, aditya siram wrote:
Normally yes, but here we are guaranteed to get a 'Just ...' value because of the 'isNothing' guard. -deech
You are correct, but that's not the point. Every time you use fromJust (or head, or unsafePerformIO...) you shift the burden of proving that it is safe from the compiler onto yourself. It's like going to a fancy restaurant and insisting on going into the kitchen and cooking your own meal. -Brent
On Thu, Aug 5, 2010 at 5:47 PM, Brent Yorgey
wrote: On Thu, Aug 05, 2010 at 05:42:40PM -0500, aditya siram wrote:
brS :: Maybe Int -> String -> String brS i ss | isNothing i = ss | otherwise = (take (fromJust i) ss) ++ (brS newIndex newStr) where newIndex = findIndex eqD newStr newStr = drop ((fromJust i) +1) ss
/me makes deech write on the blackboard 100 times, "I will not use fromJust" _______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

"Brent" == Brent Yorgey
writes:
Brent> On Thu, Aug 05, 2010 at 06:20:06PM -0500, aditya siram wrote: >> Normally yes, but here we are guaranteed to get a 'Just ...' >> value because of the 'isNothing' guard. -deech Brent> You are correct, but that's not the point. Every time you Brent> use fromJust (or head, or unsafePerformIO...) you shift the Brent> burden of proving that it is safe from the compiler onto Brent> yourself. But the compiler could indeed prove that it's safe, if the typing system reflected the precondition. Since Haskell allows programming with partial functions, you always have this burden at present. -- Colin Adams Preston Lancashire () ascii ribbon campaign - against html e-mail /\ www.asciiribbon.org - against proprietary attachments

On Fri, Aug 06, 2010 at 09:40:05AM +0100, Colin Paul Adams wrote:
"Brent" == Brent Yorgey
writes: Brent> On Thu, Aug 05, 2010 at 06:20:06PM -0500, aditya siram wrote: >> Normally yes, but here we are guaranteed to get a 'Just ...' >> value because of the 'isNothing' guard. -deech
Brent> You are correct, but that's not the point. Every time you Brent> use fromJust (or head, or unsafePerformIO...) you shift the Brent> burden of proving that it is safe from the compiler onto Brent> yourself.
But the compiler could indeed prove that it's safe, if the typing system reflected the precondition.
Sure. But it doesn't. My concern is a pragmatic one rather than theoretical. Maybe for the benefit of other beginners reading this, I should spell it out a bit more clearly rather than trying to be too cute: if you ever find yourself using fromJust, (or head, or any other functions that can sometimes cause your program to crash), you have to convince yourself that such a use is safe -- but this probably means you are doing too much work yourself, rather than letting the compiler do the work for you. You should see if there is a way to refactor your code to use pattern matching, or 'maybe', or 'fromMaybe'. In deech's particular case there was a way to pattern-match on the Maybe value (and also make the code a lot shorter at the same time) rather than using isNothing and fromJust.
Since Haskell allows programming with partial functions, you always have this burden at present.
Yes. But that doesn't mean there isn't value in the discipline of avoiding them. The burden of making sure you never use fromJust (or head, or ...) is much lighter than the burden of proving that every such use is safe. -Brent

"Brent" == Brent Yorgey
writes:
>> Since Haskell allows programming with partial functions, you >> always have this burden at present. Brent> Yes. But that doesn't mean there isn't value in the Brent> discipline of avoiding them. The burden of making sure you Brent> never use fromJust (or head, or ...) is much lighter than the Brent> burden of proving that every such use is safe. The burden is knowing whether or not a function is partial. It's that or ... that is the problem. This isn't flagged anywhere. -- Colin Adams Preston Lancashire () ascii ribbon campaign - against html e-mail /\ www.asciiribbon.org - against proprietary attachments

On Fri, Aug 06, 2010 at 11:15:52AM +0100, Colin Paul Adams wrote:
"Brent" == Brent Yorgey
writes: >> Since Haskell allows programming with partial functions, you >> always have this burden at present.
Brent> Yes. But that doesn't mean there isn't value in the Brent> discipline of avoiding them. The burden of making sure you Brent> never use fromJust (or head, or ...) is much lighter than the Brent> burden of proving that every such use is safe.
The burden is knowing whether or not a function is partial. It's that or ... that is the problem. This isn't flagged anywhere.
That's a very good point. But it's the sort of thing you pick up pretty quickly, I think. Here are some off the top of my head, for beginners reading this who might not already know: fromJust head tail init last (!!) For a fuller list, take a look at the 'safe' package on Hackage [1], which also provides many different safe alternatives. -Brent [1] http://hackage.haskell.org/package/safe

On Fri, 6 Aug 2010 13:38:56 +0100
Brent Yorgey
you shift the burden of proving that it is safe from the compiler onto yourself ... Here are some off the top of my head, for beginners reading this who might not already know:
fromJust head tail init last (!!)
i'm trying to follow this conversation. the problem is that some of these functions don't behave nicely for some inputs right? like tail [] also, is it better to use pattern matching (x:xs) than head and tail? could that be part of the point here too? -- In friendship, prad ... with you on your journey Towards Freedom http://www.towardsfreedom.com (website) Information, Inspiration, Imagination - truly a site for soaring I's

On Fri, Aug 06, 2010 at 09:06:24PM -0700, prad wrote:
On Fri, 6 Aug 2010 13:38:56 +0100 Brent Yorgey
wrote: you shift the burden of proving that it is safe from the compiler onto yourself ... Here are some off the top of my head, for beginners reading this who might not already know:
fromJust head tail init last (!!)
i'm trying to follow this conversation. the problem is that some of these functions don't behave nicely for some inputs right? like tail []
All of these functions are "partial", which means that they are undefined (crash with an error) for some inputs. If possible you should try to program only with "total" functions (functions which are defined for every input) since then you know your program will not crash.
also, is it better to use pattern matching (x:xs) than head and tail? could that be part of the point here too?
Yes, that's exactly right. -Brent

On Sat, 7 Aug 2010 09:26:10 +0100
Brent Yorgey
also, is it better to use pattern matching (x:xs) than head and tail? could that be part of the point here too?
Yes, that's exactly right.
ok thx! inspired by this i'm minimizing using head and tail everywhere i can. i like pattern matching even when the expression becomes complex because you see what you get more easily, imho. there are some rare situations where i've used head, but only because it would be very awkward to try to pattern match. -- In friendship, prad ... with you on your journey Towards Freedom http://www.towardsfreedom.com (website) Information, Inspiration, Imagination - truly a site for soaring I's

Doesn't the -Wall flag pick that up?
-deech
On 8/6/10, Colin Paul Adams
"Brent" == Brent Yorgey
writes: >> Since Haskell allows programming with partial functions, you >> always have this burden at present.
Brent> Yes. But that doesn't mean there isn't value in the Brent> discipline of avoiding them. The burden of making sure you Brent> never use fromJust (or head, or ...) is much lighter than the Brent> burden of proving that every such use is safe.
The burden is knowing whether or not a function is partial. It's that or ... that is the problem. This isn't flagged anywhere. -- Colin Adams Preston Lancashire () ascii ribbon campaign - against html e-mail /\ www.asciiribbon.org - against proprietary attachments

"Daniel" == Daniel Fischer
writes:
Daniel> On Friday 06 August 2010 14:52:06, aditya siram wrote: >> Doesn't the -Wall flag pick that up? -deech Daniel> Not if there's an explicit error call for the undefined Daniel> cases, e.g. Daniel> head :: [a] -> a head (x:_) = x head _ = error Daniel> "Prelude.head: empty list" Daniel> compiles without warning. Ah. So it's safer not to use defensive programming then. Good. As an Eiffel programmer, that's what I'm used to. -- Colin Adams Preston Lancashire () ascii ribbon campaign - against html e-mail /\ www.asciiribbon.org - against proprietary attachments

On Thu, Aug 05, 2010 at 03:22:35PM -0700, prad wrote:
i'm trying to create my own split function with % as delimiter. so i have eqD = (=='%')
and send
let s = "zaoeu%aeuasnt%staashaeu%nthdanoe%nthd" putStrLn $ show $ brS (findIndex eqD s) s
to a function brS:
brS i ss | isNothing i = ss | otherwise = (take i ss) : (brS newIndex newStr) where newIndex = findIndex eqD newStr newStr = drop (i+1) ss
Because of the (i+1) argument to drop, GHC infers that i must be an Int. Because i is used as an argument to isNothing, GHC infers that i must have the type (Maybe a) for some type a. It cannot be both. If I were you I would define brS by pattern matching, like so: brS Nothing ss = ss brS (Just i) ss = ... Now in the ... i really will be an Int. Also, did you know there is already code to do this in the 'split' package on Hackage? (Just 'cabal install split' and look at the 'Data.List.Split' module.) But if you're just writing this function in order to learn, then no problem. -Brent

On Thu, 5 Aug 2010 23:39:23 +0100
Brent Yorgey
Also, did you know there is already code to do this in the 'split' package on Hackage? (Just 'cabal install split' and look at the 'Data.List.Split' module.)
thx brent. i've looked at various goodies from cabal and am trying to understand the code. for instance, there is a split function in Useful that i was trying to figure out as well as a replace (which is what this is eventually going to develop into). i'm just trying to see if i can get a better understanding by coming up with my own versions as well. unfortunately, i had no clue about the issue with mayBe and how to deal with findIndex. though this Just Int and Nothing business is an inconvenience presently, it feels somehow more honest that what some languages do where if something isn't found the function returns 0. thank you for your explanation too as well as those by deech and jurgen. they've cleared up several things. -- In friendship, prad ... with you on your journey Towards Freedom http://www.towardsfreedom.com (website) Information, Inspiration, Imagination - truly a site for soaring I's

El jue, 05-08-2010 a las 15:22 -0700, prad escribió:
i'm trying to create my own split function with % as delimiter. so i have eqD = (=='%')
and send
let s = "zaoeu%aeuasnt%staashaeu%nthdanoe%nthd" putStrLn $ show $ brS (findIndex eqD s) s
to a function brS:
brS i ss | isNothing i = ss | otherwise = (take i ss) : (brS newIndex newStr) where newIndex = findIndex eqD newStr newStr = drop (i+1) ss
but get the following error:
Couldn't match expected type `Maybe a' against inferred type `Int' In the first argument of `isNothing', namely `i' In the expression: isNothing i :: mayBe a In a stmt of a pattern guard for the definition of `brS': isNothing i :: mayBe a
my understanding is that i need the isNothing because findIndex will return Just Int or Nothing.
Yes. But ghc is telling you that 'i' should have type Maybe a, whereas it has the type Int. look at the following line: | otherwise = (take i ss) : (brS newIndex newStr) the 'take i ss' tells ghc that i is an Int. the 'brs newIndex newStr' tells ghc that i has the same type as newIndex. now: newIndex = findIndex eqD newStr this tells ghc that newIndex has type Maybe Int, which does not match the type Int inferred above. You would have to fix the definition of newIndex. But really, you are doing it the wrong way. Your code is traversing the list once to find sth. (the findIndex ...), and then traversing it again to split it (the take i ...). Why not split directly when you find what you are looking for? Jürgen

On Fri, 06 Aug 2010 00:52:51 +0200
Jürgen Doser
But really, you are doing it the wrong way. Your code is traversing the list once to find sth. (the findIndex ...), and then traversing it again to split it (the take i ...). Why not split directly when you find what you are looking for?
ya i will think about this now that the other issue has been explained! the way i was doing it seemed a bit funny (and i initially tried findIndices), but couldn't see how to use the limited tools i'm aware of. i was wanting to do something like keep pulling characters and make a new string until the delimiter was found fn cs = [x | x <- cs, x /= '%'] : [] but can't figure out how to use this idea to actually cause splitting into [String] i also explored break and splitAt, but haven't quite worked out a mechanism to use those, yet. thx again for your help. -- In friendship, prad ... with you on your journey Towards Freedom http://www.towardsfreedom.com (website) Information, Inspiration, Imagination - truly a site for soaring I's

El jue, 05-08-2010 a las 17:08 -0700, prad escribió:
i was wanting to do something like keep pulling characters and make a new string until the delimiter was found
"keep pulling ... until the delimiter was found" sounds suspiciously like takeWhile and friends (like break, see below).
fn cs = [x | x <- cs, x /= '%'] : []
This doesn't split, it just filters. In particular, you have no way of knowing where in the string elements where discarded.
but can't figure out how to use this idea to actually cause splitting into [String]
Neither do I :)
i also explored break and splitAt, but haven't quite worked out a mechanism to use those, yet.
break is exactly what I would use. The only problem is that break will only look for the first delimiter match. To get all the matches, you will have to get the recursion right... For practice purposes, in particular for getting used to recursion, it might also be useful to write the function without any help of library functions, traversing the string using direct recursion only. For every character you encounter, what do you have to do in each case? Jürgen

On Fri, 06 Aug 2010 02:44:26 +0200
Jürgen Doser
For practice purposes, in particular for getting used to recursion, it might also be useful to write the function without any help of library functions, traversing the string using direct recursion only. For every character you encounter, what do you have to do in each case?
you are a good teacher, jurgen! here's what i came up with: br [] = [] br ss = fst (tup) : br (tail (snd tup)) where tup = break eqD ss now this works great for let s = "zaoeu%aeuasnt%staashaeu%nthdanoe%nthd%" but i get a *** Exception: Prelude.tail: empty list i found a neat way to explore recursion on ghci like this Prelude> let s = "aoeu%snthi%ashuet" Prelude> break (=='%') s ("aoeu","%snthi%ashuet") Prelude> break (=='%') (tail (snd it)) ("snthi","%ashuet") Prelude> break (=='%') (tail (snd it)) ("ashuet","") Prelude> break (=='%') (tail (snd it)) *** Exception: Prelude.tail: empty list of course this is the problem i'm having in that i'm forced to take the tail of an empty list at the end. correcting it by sticking on a delimiter doesn't seem to be the right thing to do though. so there must be another way to deal with this. hmmm. -- In friendship, prad ... with you on your journey Towards Freedom http://www.towardsfreedom.com (website) Information, Inspiration, Imagination - truly a site for soaring I's

On Thu, 5 Aug 2010 19:07:13 -0700
prad
correcting it by sticking on a delimiter doesn't seem to be the right thing to do though. so there must be another way to deal with this. hmmm.
i think i can solve the dilemma by introducing an accessory function getTail: br [] = [] br ss = fst (tup) : br (getTail (snd tup)) where tup = break eqD ss getTail s | s==[] = [] | otherwise = tail s it works, though i don't know if this is necessarily the best way to do it. -- In friendship, prad ... with you on your journey Towards Freedom http://www.towardsfreedom.com (website) Information, Inspiration, Imagination - truly a site for soaring I's

At 8:34 PM -0700 8/5/10, prad wrote:
On Thu, 5 Aug 2010 19:07:13 -0700 prad
wrote: correcting it by sticking on a delimiter doesn't seem to be the right thing to do though. so there must be another way to deal with this. hmmm.
i think i can solve the dilemma by introducing an accessory function getTail:
br [] = [] br ss = fst (tup) : br (getTail (snd tup)) where tup = break eqD ss getTail s | s==[] = [] | otherwise = tail s
it works, though i don't know if this is necessarily the best way to do it.
-- In friendship, prad
I would write something like: br [] = [] br ss = let (h, t) = break eqD ss in h : case t of [] -> [] _ : t -> br t Dean

On Fri, 6 Aug 2010 03:43:30 -0400
Dean Herington
I would write something like:
br [] = [] br ss = let (h, t) = break eqD ss in h : case t of [] -> [] _ : t -> br t
thx dean. that certainly looks cleaner than mine, but i'm not sure i have seen this construct before. i thought let/in was used like this: aaa = let y = 1+2 z = 4+6 in y+z which is like aaa = y + z where y = 1+2 z = 4+6 in other words, you just define the parts first and use the "in" to define the main expression. but here it seems you are defining what appears to be the main item let (h,t) = break eqD ss to get the tuple parts and then forming your array (which really is the main item) using these parts as h : t with t being given 2 options. this is very interesting to me as i had not seen such a construct before. -- In friendship, prad ... with you on your journey Towards Freedom http://www.towardsfreedom.com (website) Information, Inspiration, Imagination - truly a site for soaring I's

At 11:04 AM -0700 8/6/10, prad wrote:
On Fri, 6 Aug 2010 03:43:30 -0400 Dean Herington
wrote: I would write something like:
br [] = [] br ss = let (h, t) = break eqD ss in h : case t of [] -> [] _ : t -> br t
thx dean. that certainly looks cleaner than mine, but i'm not sure i have seen this construct before.
i thought let/in was used like this:
aaa = let y = 1+2 z = 4+6 in y+z
which is like
aaa = y + z where y = 1+2 z = 4+6
in other words, you just define the parts first and use the "in" to define the main expression.
but here it seems you are defining what appears to be the main item let (h,t) = break eqD ss to get the tuple parts and then forming your array (which really is the main item) using these parts as h : t with t being given 2 options.
this is very interesting to me as i had not seen such a construct before.
Choosing between `let` and `where` is usually a matter of taste. I use both, depending on whether I think it's clearer to present the logic "bottom-up" or "top-down". Here's the `where`-style equivalent of the `let` version: br [] = [] br ss = h : case t of [] -> [] _ : t' -> br t' where (h, t) = break eqD ss For a reason I probably can't articulate well, I find the `let` version more readable in this case. Perhaps it's because I understand the function as (1) `break`ing on '%', then (2) dealing with the details of recursing. Cheers, Dean
participants (7)
-
aditya siram
-
Brent Yorgey
-
Colin Paul Adams
-
Daniel Fischer
-
Dean Herington
-
Jürgen Doser
-
prad