Dne 09/01/2013 09:13 PM, Harald Bögeholz napsal(a):
Am 31.08.13 14:35, schrieb Petr Pudlák:
One solution would be to fold over a specific semigroup instead of a
recursive function:

|import  Data.Semigroup
import  Data.Foldable(foldMap)
import  Data.Maybe(maybeToList)

data  Darle  a =Darle  {getInit  :: [a],getLast  ::a  }
   deriving  Show
instance  Semigroup  (Darle  a)where
     ~(Darle  xs1 l1) <> ~(Darle  xs2 l2) =Darle  (xs1 ++ [l1] ++ xs2) l2

darle  :: [a] ->Darle  a
darle  = foldr1 (<>) . map (Darle  [])|

It's somewhat more verbose, but the core idea is clearly expressed in
the one line that defines |<>|, and IMHO it better shows /what/ are we
doing rather than /how/. It's sufficiently lazy so that you can do
something like |head . getInit $ darle [1..]|.
I am wondering why you put the Semigroup instance there and what the
other imports are for. Doesn't this work just as well?
Sorry, the two other imports are redundant, I forgot to erase them when playing with various ideas.

The Semigroup instance of course isn't necessary for this particular purpose. But having it (1) signals that the operation satisfies some laws (associativity) and (2) allows the structure to be reused anywhere where a Semigroup is required.

For example, we can wrap it into `Option` to get a monoid, and perhaps use it in `foldMap`. This way we extend the functionality to empty collections:
```haskell
darle :: Foldable f => f a -> Maybe (Darle a)
darle = getOption . foldMap (Option . Just . Darle [])
```

  Best regards,
  Petr


_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to