Skip to content

Commit

Permalink
Fix warnings, fixes #17
Browse files Browse the repository at this point in the history
Dependencies still produce lots of warnings. *shrug*
  • Loading branch information
hdgarrood committed Nov 14, 2015
1 parent 1450406 commit e3c3707
Show file tree
Hide file tree
Showing 3 changed files with 9 additions and 9 deletions.
3 changes: 2 additions & 1 deletion bower.json
Original file line number Diff line number Diff line change
Expand Up @@ -32,7 +32,8 @@
"purescript-control": "^0.3.0",
"purescript-identity": "^0.4.0",
"purescript-profunctor": "^0.3.0",
"purescript-unsafe-coerce": "^0.1.0"
"purescript-unsafe-coerce": "^0.1.0",
"purescript-exceptions": "^0.3.1"
},
"devDependencies": {
"purescript-quickcheck": "^0.11.0",
Expand Down
2 changes: 2 additions & 0 deletions src/Data/FingerTree.purs
Original file line number Diff line number Diff line change
Expand Up @@ -59,6 +59,7 @@ import Data.Monoid (Monoid, mempty)
import Data.Traversable (Traversable, traverse)
import Data.Tuple (Tuple(Tuple))
import Data.Unfoldable (Unfoldable, unfoldr)
import Control.Monad.Eff.Exception.Unsafe (unsafeThrow)

import Data.Sequence.Internal (Measured, (!), (<$$$>), measure)

Expand Down Expand Up @@ -406,6 +407,7 @@ unsafeSplitDigit p i as =
unsafeSplitTree :: forall a v. (Monoid v, Measured a v) =>
(v -> Boolean) -> v -> FingerTree v a -> LazySplit (FingerTree v) a
unsafeSplitTree p i (Single x) = LazySplit lazyEmpty x lazyEmpty
unsafeSplitTree _ _ Empty = unsafeThrow "Data.FingerTree.unsafeSplitTree: Empty"
unsafeSplitTree p i (Deep _ pr m sf) =
let vpr = i <> measure pr
in if p vpr
Expand Down
13 changes: 5 additions & 8 deletions src/Data/Sequence/NonEmpty.purs
Original file line number Diff line number Diff line change
Expand Up @@ -47,8 +47,9 @@ import Prelude hiding (append)
import Control.Alt (Alt)
import Data.Foldable (Foldable, foldl, foldMap, foldr)
import Data.Maybe (Maybe(Just, Nothing), maybe)
import Data.Maybe.Unsafe (fromJust)
import Data.Traversable (Traversable, sequence, traverse)
import Data.Tuple (Tuple(Tuple), fst)
import Data.Tuple (Tuple(Tuple), fst, uncurry)
import Data.Unfoldable (Unfoldable)

import qualified Data.Sequence as S
Expand Down Expand Up @@ -167,9 +168,7 @@ fromSeq :: forall f a. (Functor f, Unfoldable f) => Seq a -> f a
fromSeq = S.fromSeq <<< toPlain

fromPlainUnsafe :: forall a. S.Seq a -> Seq a
fromPlainUnsafe xs =
case S.uncons xs of
Just (Tuple x xs) -> Seq x xs
fromPlainUnsafe = S.uncons >>> fromJust >>> uncurry Seq

instance showSeq :: (Show a) => Show (Seq a) where
show (Seq x xs) = "(Seq " <> show x <> " " <> show xs <> ")"
Expand Down Expand Up @@ -208,8 +207,6 @@ instance foldableSeq :: Foldable Seq where
foldl f z = toPlain >>> foldl f z
foldMap f = toPlain >>> foldMap f

fmap = (<$>)

instance traversableSeq :: Traversable Seq where
sequence = toPlain >>> sequence >>> fmap fromPlainUnsafe
traverse f = toPlain >>> traverse f >>> fmap fromPlainUnsafe
sequence = toPlain >>> sequence >>> map fromPlainUnsafe
traverse f = toPlain >>> traverse f >>> map fromPlainUnsafe

0 comments on commit e3c3707

Please sign in to comment.