Skip to content
Merged
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
67 changes: 66 additions & 1 deletion README.md
Original file line number Diff line number Diff line change
@@ -1,5 +1,27 @@
# Module Documentation

## Module Control.Alt

### Type Classes

class (Functor f) <= Alt f where
(<|>) :: forall a. f a -> f a -> f a


## Module Control.Alternative

### Type Classes

class (Applicative f, Plus f) <= Alternative f where


### Values

many :: forall f a. (Alternative f, Lazy1 f) => f a -> f [a]

some :: forall f a. (Alternative f, Lazy1 f) => f a -> f [a]


## Module Control.Apply

### Values
Expand Down Expand Up @@ -34,6 +56,29 @@
join :: forall a m. (Bind m) => m (m a) -> m a


## Module Control.Lazy

### Type Classes

class Lazy l where
defer :: (Unit -> l) -> l

class Lazy1 l where
defer1 :: forall a. (Unit -> l a) -> l a

class Lazy2 l where
defer2 :: forall a b. (Unit -> l a b) -> l a b


### Values

fix :: forall l a. (Lazy l) => (l -> l) -> l

fix1 :: forall l a. (Lazy1 l) => (l a -> l a) -> l a

fix2 :: forall l a b. (Lazy2 l) => (l a b -> l a b) -> l a b


## Module Control.Monad

### Values
Expand All @@ -44,4 +89,24 @@

unless :: forall m. (Monad m) => Boolean -> m Unit -> m Unit

when :: forall m. (Monad m) => Boolean -> m Unit -> m Unit
when :: forall m. (Monad m) => Boolean -> m Unit -> m Unit


## Module Control.MonadPlus

### Type Classes

class (Monad m, Alternative m) <= MonadPlus m where


### Values

guard :: forall m. (MonadPlus m) => Boolean -> m Unit


## Module Control.Plus

### Type Classes

class (Alt f) <= Plus f where
empty :: forall a. f a
6 changes: 6 additions & 0 deletions src/Control/Alt.purs
Original file line number Diff line number Diff line change
@@ -0,0 +1,6 @@
module Control.Alt where

infixl 3 <|>

class (Functor f) <= Alt f where
(<|>) :: forall a. f a -> f a -> f a
14 changes: 14 additions & 0 deletions src/Control/Alternative.purs
Original file line number Diff line number Diff line change
@@ -0,0 +1,14 @@
module Control.Alternative where

import Control.Alt
import Control.Lazy
import Control.Plus

class (Applicative f, Plus f) <= Alternative f

some :: forall f a. (Alternative f, Lazy1 f) => f a -> f [a]
some v = (:) <$> v <*> defer1 (\_ -> many v)

many :: forall f a. (Alternative f, Lazy1 f) => f a -> f [a]
many v = some v <|> pure []
Copy link
Contributor

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

These look like they won't terminate.

Copy link
Member Author

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Oops, of course. I meant to come back to these.

Copy link
Contributor

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

I would like to find a way to keep these though, because they're obviously very useful. In parsing, I wrote a special combinator, but I think if we have a type class which captures laziness, we can do it.

Copy link
Contributor

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Copy link
Member Author

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Perhaps something to add to purescript-lazy then? I guess we'd prefer control to have no dependencies though, considering a lot of stuff is going to be depending on it...

Copy link
Contributor

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

I think it's fine in control. It's not an implementation of laziness.

Copy link
Member Author

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Control.Lazy then? That might be extremely useful actually.

Copy link
Contributor

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Sure. I think there might also be use for a whole set of type classes along these lines: Lazy, Lazy1, etc. but for now, just the two is probably enough :)


19 changes: 19 additions & 0 deletions src/Control/Lazy.purs
Original file line number Diff line number Diff line change
@@ -0,0 +1,19 @@
module Control.Lazy where

class Lazy l where
defer :: (Unit -> l) -> l

class Lazy1 l where
defer1 :: forall a. (Unit -> l a) -> l a

class Lazy2 l where
defer2 :: forall a b. (Unit -> l a b) -> l a b

fix :: forall l a. (Lazy l) => (l -> l) -> l
fix f = defer (\_ -> f (fix f))

fix1 :: forall l a. (Lazy1 l) => (l a -> l a) -> l a
fix1 f = defer1 (\_ -> f (fix1 f))

fix2 :: forall l a b. (Lazy2 l) => (l a b -> l a b) -> l a b
fix2 f = defer2 (\_ -> f (fix2 f))
10 changes: 10 additions & 0 deletions src/Control/MonadPlus.purs
Original file line number Diff line number Diff line change
@@ -0,0 +1,10 @@
module Control.MonadPlus where

import Control.Alternative
import Control.Plus

class (Monad m, Alternative m) <= MonadPlus m

guard :: forall m. (MonadPlus m) => Boolean -> m Unit
Copy link
Contributor

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Finally! Now I can add this to the book under array comprehensions :)

guard true = return unit
guard false = empty
6 changes: 6 additions & 0 deletions src/Control/Plus.purs
Original file line number Diff line number Diff line change
@@ -0,0 +1,6 @@
module Control.Plus where

import Control.Alt

class (Alt f) <= Plus f where
empty :: forall a. f a