| Safe Haskell | Safe |
|---|---|
| Language | Haskell2010 |
Tip.Prelude
Contents
Description
A drop-in replacement for Prelude with unfoldings exported, oriented towards Nats
- module Tip
- otherwise :: Bool
- (&&) :: Bool -> Bool -> Bool
- (||) :: Bool -> Bool -> Bool
- not :: Bool -> Bool
- data Nat
- even :: Nat -> Bool
- double :: Nat -> Nat
- half :: Nat -> Nat
- (+) :: Nat -> Nat -> Nat
- (*) :: Nat -> Nat -> Nat
- (^) :: Nat -> Nat -> Nat
- (-) :: Nat -> Nat -> Nat
- (<) :: Nat -> Nat -> Bool
- (<=) :: Nat -> Nat -> Bool
- (>) :: Nat -> Nat -> Bool
- (>=) :: Nat -> Nat -> Bool
- (==) :: Nat -> Nat -> Bool
- (/=) :: Nat -> Nat -> Bool
- max :: Nat -> Nat -> Nat
- min :: Nat -> Nat -> Nat
- take :: Nat -> [a] -> [a]
- drop :: Nat -> [a] -> [a]
- splitAt :: Nat -> [a] -> ([a], [a])
- length :: [a] -> Nat
- delete :: Nat -> [Nat] -> [Nat]
- deleteAll :: Nat -> [Nat] -> [Nat]
- count :: Nat -> [Nat] -> Nat
- nub :: [Nat] -> [Nat]
- index :: [a] -> Nat -> Maybe a
- elem :: Nat -> [Nat] -> Bool
- isPermutation :: [Nat] -> [Nat] -> Bool
- sorted :: [Nat] -> Bool
- ordered :: [Nat] -> Bool
- uniqsorted :: [Nat] -> Bool
- unique :: [Nat] -> Bool
- insert :: Nat -> [Nat] -> [Nat]
- isort :: [Nat] -> [Nat]
- eqList :: [Nat] -> [Nat] -> Bool
- sum :: [Nat] -> Nat
- product :: [Nat] -> Nat
- lookup :: Nat -> [(Nat, b)] -> Maybe b
- zeq :: Int -> Int -> Bool
- zne :: Int -> Int -> Bool
- zle :: Int -> Int -> Bool
- zlt :: Int -> Int -> Bool
- zgt :: Int -> Int -> Bool
- zge :: Int -> Int -> Bool
- zplus :: Int -> Int -> Int
- zmult :: Int -> Int -> Int
- zminus :: Int -> Int -> Int
- zmax :: Int -> Int -> Int
- zmin :: Int -> Int -> Int
- ztake :: Int -> [a] -> [a]
- zdrop :: Int -> [a] -> [a]
- zsplitAt :: Int -> [a] -> ([a], [a])
- zlength :: [a] -> Int
- zdelete :: Int -> [Int] -> [Int]
- zdeleteAll :: Int -> [Int] -> [Int]
- zcount :: Int -> [Int] -> Nat
- zzcount :: Int -> [Int] -> Int
- znub :: [Int] -> [Int]
- zindex :: [a] -> Int -> Maybe a
- zelem :: Int -> [Int] -> Bool
- zisPermutation :: [Int] -> [Int] -> Bool
- zsorted :: [Int] -> Bool
- zordered :: [Int] -> Bool
- zuniqsorted :: [Int] -> Bool
- zunique :: [Int] -> Bool
- zinsert :: Int -> [Int] -> [Int]
- zisort :: [Int] -> [Int]
- zeqList :: [Int] -> [Int] -> Bool
- zsum :: [Int] -> Int
- zproduct :: [Int] -> Int
- zlookup :: Int -> [(Int, b)] -> Maybe b
- null :: [a] -> Bool
- (++) :: [a] -> [a] -> [a]
- reverse :: [a] -> [a]
- zip :: [a] -> [b] -> [(a, b)]
- filter :: (a -> Bool) -> [a] -> [a]
- map :: (a -> b) -> [a] -> [b]
- concat :: [[a]] -> [a]
- concatMap :: (a -> [b]) -> [a] -> [b]
- foldl :: (b -> a -> b) -> b -> [a] -> b
- foldr :: (a -> b -> b) -> b -> [a] -> b
- and :: [Bool] -> Bool
- or :: [Bool] -> Bool
- all :: (a -> Bool) -> [a] -> Bool
- any :: (a -> Bool) -> [a] -> Bool
- takeWhile :: (a -> Bool) -> [a] -> [a]
- dropWhile :: (a -> Bool) -> [a] -> [a]
- id :: a -> a
- const :: a -> b -> a
- (.) :: (b -> c) -> (a -> b) -> a -> c
- flip :: (a -> b -> c) -> b -> a -> c
- ($) :: (a -> b) -> a -> b
- maybe :: b -> (a -> b) -> Maybe a -> b
- either :: (a -> c) -> (b -> c) -> Either a b -> c
- fst :: (a, b) -> a
- snd :: (a, b) -> b
- data Bool :: *
- data Maybe a :: * -> *
- data Either a b :: * -> * -> *
- data Int :: *
Documentation
module Tip
Booleans
Nat functions
Truncated subtraction
List functions on nats
isPermutation :: [Nat] -> [Nat] -> Bool Source
uniqsorted :: [Nat] -> Bool Source
Int functions
List functions on Ints
zdeleteAll :: Int -> [Int] -> [Int] Source
zisPermutation :: [Int] -> [Int] -> Bool Source
zuniqsorted :: [Int] -> Bool Source
Polymorphic lists functions
Lists and booleans
data Bool :: *
Instances
| Bounded Bool | |
| Enum Bool | |
| Eq Bool | |
| Ord Bool | |
| Show Bool | |
| Ix Bool | |
| Generic Bool | |
| Testable Bool | |
| Arbitrary Bool | |
| CoArbitrary Bool | |
| Outputable Bool | |
| Quasi U | |
| Lift Bool | |
| Testable (Neg Bool) | |
| Testable b => Testable ((:=>:) Bool b) | |
| Testable b => Testable ((:=>:) (Neg Bool) b) | |
| type Rep Bool = D1 D1Bool ((:+:) (C1 C1_0Bool U1) (C1 C1_1Bool U1)) | |
| type (==) Bool a b = EqBool a b |
data Maybe a :: * -> *
The Maybe type encapsulates an optional value. A value of type
either contains a value of type Maybe aa (represented as ),
or it is empty (represented as Just aNothing). Using Maybe is a good way to
deal with errors or exceptional cases without resorting to drastic
measures such as error.
The Maybe type is also a monad. It is a simple kind of error
monad, where all errors are represented by Nothing. A richer
error monad can be built using the Either type.
Instances
| Monad Maybe | |
| Functor Maybe | |
| Applicative Maybe | |
| Foldable Maybe | |
| Traversable Maybe | |
| Generic1 Maybe | |
| Alternative Maybe | |
| MonadPlus Maybe | |
| Eq1 Maybe | |
| Ord1 Maybe | |
| Read1 Maybe | |
| Show1 Maybe | |
| UserOfRegs r a => UserOfRegs r (Maybe a) | |
| DefinerOfRegs r a => DefinerOfRegs r (Maybe a) | |
| Eq a => Eq (Maybe a) | |
| Ord a => Ord (Maybe a) | |
| Show a => Show (Maybe a) | |
| Generic (Maybe a) | |
| Arbitrary a => Arbitrary (Maybe a) | |
| CoArbitrary a => CoArbitrary (Maybe a) | |
| Monoid a => Monoid (Maybe a) | Lift a semigroup into |
| Outputable a => Outputable (Maybe a) | |
| Lift a => Lift (Maybe a) | |
| type Rep1 Maybe = D1 D1Maybe ((:+:) (C1 C1_0Maybe U1) (C1 C1_1Maybe (S1 NoSelector Par1))) | |
| type Rep (Maybe a) = D1 D1Maybe ((:+:) (C1 C1_0Maybe U1) (C1 C1_1Maybe (S1 NoSelector (Rec0 a)))) | |
| type (==) (Maybe k) a b = EqMaybe k a b |
data Either a b :: * -> * -> *
The Either type represents values with two possibilities: a value of
type is either Either a b or Left a.Right b
The Either type is sometimes used to represent a value which is
either correct or an error; by convention, the Left constructor is
used to hold an error value and the Right constructor is used to
hold a correct value (mnemonic: "right" also means "correct").
Examples
The type is the type of values which can be either
a Either String IntString or an Int. The Left constructor can be used only on
Strings, and the Right constructor can be used only on Ints:
>>>let s = Left "foo" :: Either String Int>>>sLeft "foo">>>let n = Right 3 :: Either String Int>>>nRight 3>>>:type ss :: Either String Int>>>:type nn :: Either String Int
The fmap from our Functor instance will ignore Left values, but
will apply the supplied function to values contained in a Right:
>>>let s = Left "foo" :: Either String Int>>>let n = Right 3 :: Either String Int>>>fmap (*2) sLeft "foo">>>fmap (*2) nRight 6
The Monad instance for Either allows us to chain together multiple
actions which may fail, and fail overall if any of the individual
steps failed. First we'll write a function that can either parse an
Int from a Char, or fail.
>>>import Data.Char ( digitToInt, isDigit )>>>:{let parseEither :: Char -> Either String Int parseEither c | isDigit c = Right (digitToInt c) | otherwise = Left "parse error">>>:}
The following should work, since both '1' and '2' can be
parsed as Ints.
>>>:{let parseMultiple :: Either String Int parseMultiple = do x <- parseEither '1' y <- parseEither '2' return (x + y)>>>:}
>>>parseMultipleRight 3
But the following should fail overall, since the first operation where
we attempt to parse 'm' as an Int will fail:
>>>:{let parseMultiple :: Either String Int parseMultiple = do x <- parseEither 'm' y <- parseEither '2' return (x + y)>>>:}
>>>parseMultipleLeft "parse error"
Instances
| MonadError e (Either e) | |
| Monad (Either e) | |
| Functor (Either a) | |
| Applicative (Either e) | |
| Foldable (Either a) | |
| Traversable (Either a) | |
| Generic1 (Either a) | |
| Eq a => Eq1 (Either a) | |
| Ord a => Ord1 (Either a) | |
| Read a => Read1 (Either a) | |
| Show a => Show1 (Either a) | |
| (Eq a, Eq b) => Eq (Either a b) | |
| (Ord a, Ord b) => Ord (Either a b) | |
| (Read a, Read b) => Read (Either a b) | |
| (Show a, Show b) => Show (Either a b) | |
| Generic (Either a b) | |
| (Arbitrary a, Arbitrary b) => Arbitrary (Either a b) | |
| (CoArbitrary a, CoArbitrary b) => CoArbitrary (Either a b) | |
| (Outputable a, Outputable b) => Outputable (Either a b) | |
| (Lift a, Lift b) => Lift (Either a b) | |
| (PrettyVar a, PrettyVar b) => PrettyVar (Either a b) | |
| type Rep1 (Either a) = D1 D1Either ((:+:) (C1 C1_0Either (S1 NoSelector (Rec0 a))) (C1 C1_1Either (S1 NoSelector Par1))) | |
| type Rep (Either a b) = D1 D1Either ((:+:) (C1 C1_0Either (S1 NoSelector (Rec0 a))) (C1 C1_1Either (S1 NoSelector (Rec0 b)))) | |
| type (==) (Either k k1) a b = EqEither k k1 a b |