Skip to content

Commit

Permalink
final fix for (/)
Browse files Browse the repository at this point in the history
Ignore-this: 4093b2cacfc62f8019befb9e9f289ffc

darcs-hash:20100614090038-7b3c0-ac86a759b86a0d3611f71ba9372df86b8cc3535c.gz
  • Loading branch information
ekmett authored and Barak A. Pearlmutter committed Jun 14, 2010
1 parent ae53922 commit b511b3d
Show file tree
Hide file tree
Showing 4 changed files with 6 additions and 7 deletions.
5 changes: 3 additions & 2 deletions Numeric/AD/Internal/Classes.hs
Expand Up @@ -35,6 +35,7 @@ infixl 7 *!, /!, ^*, *^, ^/
infixl 6 +!, -!, <+>
infix 4 ==!


class Iso a b where
iso :: f a -> f b
osi :: f b -> f a
Expand Down Expand Up @@ -199,7 +200,7 @@ deriveLifted f _t = do
abs1 = lift1 abs signum1
signum1 = lift1 signum (const zero)
fromRational1 = lift . fromRational
(/!) = lift2_ (/) $ \a x y -> (recip1 y, x *! negate1 (square1 a))
x /! y = x *! recip1 y
recip1 = lift1_ recip (const . negate1 . square1)

pi1 = lift pi
Expand All @@ -209,7 +210,7 @@ deriveLifted f _t = do
sqrt1 = lift1_ sqrt (\z _ -> recip1 (lift 2 *! z))
(**!) = lift2_ (**) (\z x y -> (y *! z /! x, z *! log1 x)) -- error at 0 ** n
sin1 = lift1 sin cos1
cos1 = lift1 cos $ \x -> negate1 (sin1 x)
cos1 = lift1 cos $ negate1 . sin1
tan1 x = sin1 x /! cos1 x
asin1 = lift1 asin $ \x -> recip1 (sqrt1 (one -! square1 x))
acos1 = lift1 acos $ \x -> negate1 (recip1 (sqrt1 (one -! square1 x)))
Expand Down
4 changes: 1 addition & 3 deletions Numeric/AD/Internal/Stream.hs
Expand Up @@ -23,7 +23,7 @@ import Data.Monoid
import Data.Foldable
import Data.Traversable
import Data.Data (Data(..), mkDataType, DataType, mkConstr, Constr, constrIndex, Fixity(Infix))
import Data.Typeable (Typeable1(..), Typeable(..), TyCon, mkTyCon, mkTyConApp, gcast1)
import Data.Typeable (Typeable1(..), TyCon, mkTyCon, mkTyConApp, gcast1)
import Numeric.AD.Internal.Comonad

infixl 3 :<
Expand All @@ -32,8 +32,6 @@ data Stream f a = a :< f (Stream f a)

deriving instance (Show a, Show (f (Stream f a))) => Show (Stream f a)

-- TODO: Data, Typeable

instance Functor f => Functor (Stream f) where
fmap f (a :< as) = f a :< fmap f <$> as

Expand Down
2 changes: 1 addition & 1 deletion Numeric/AD/Internal/Tensors.hs
Expand Up @@ -22,7 +22,7 @@ import Control.Applicative
import Data.Foldable
import Data.Traversable
import Data.Monoid
import Data.Typeable (Typeable1(..), Typeable(..), TyCon, mkTyCon, mkTyConApp)
import Data.Typeable (Typeable1(..), TyCon, mkTyCon, mkTyConApp)
import Numeric.AD.Internal.Comonad
import Numeric.AD.Internal.Stream

Expand Down
2 changes: 1 addition & 1 deletion ad.cabal
@@ -1,5 +1,5 @@
name: ad
version: 0.44.3
version: 0.44.4
license: BSD3
license-File: LICENSE
copyright: (c) Edward Kmett 2010,
Expand Down

0 comments on commit b511b3d

Please sign in to comment.